Skip to content

Instantly share code, notes, and snippets.

@larsmans
Created August 15, 2011 13:22
Show Gist options
  • Star 3 You must be signed in to star a gist
  • Fork 1 You must be signed in to fork a gist
  • Save larsmans/1146705 to your computer and use it in GitHub Desktop.
Save larsmans/1146705 to your computer and use it in GitHub Desktop.
Nonogram/paint-by-numbers solver in SWI-Prolog
/*
* Nonogram/paint-by-numbers solver in SWI-Prolog. Uses CLP(FD),
* in particular the automaton/3 (finite-state/RE) constraint.
* Copyright 2011, 2014 Lars Buitinck
* Copyright 2014 Markus Triska
* Do with this code as you like, but don't remove the copyright notice.
*/
:- use_module(library(clpfd)).
nono(RowSpec, ColSpec, Grid) :-
maplist(row, RowSpec, Grid),
transpose(Grid, GridT),
maplist(row, ColSpec, GridT).
row(Ks, Row) :-
sum(Ks, #=, Ones),
sum(Row, #=, Ones),
phrase(arcs(Ks, Start, Final), Arcs),
append(Row, [0], RowZ),
automaton(RowZ, [source(Start), sink(Final)], [arc(Start,0,Start) | Arcs]).
% List of transition arcs for finite-state constraint.
arcs([], Final, Final) --> [].
arcs([K|Ks], CurState, Final) -->
( { K == 0 } ->
[arc(CurState, 0, CurState), arc(CurState, 0, NextState)],
arcs(Ks, NextState, Final)
; [arc(CurState, 1, NextState)],
{ K1 #= K-1 },
arcs([K1|Ks], NextState, Final)
).
make_grid(Grid, X, Y, Vars) :-
length(Grid,X),
make_rows(Grid, Y, Vars).
make_rows([], _, []).
make_rows([R|Rs], Len, Vars) :-
length(R, Len),
make_rows(Rs, Len, Vars0),
append(R, Vars0, Vars).
print_row([]) :- nl.
print_row([X|R]) :-
(X == 0 ->
write(' ')
;
write('x')
),
print_row(R).
example1(10, 5,
[[2], [2,1], [1,1], [3], [1,1], [1,1], [2], [1,1], [1,2], [2]],
[[2,1], [2,1,3], [7], [1,3], [2,1]]).
go :-
example1(X, Y, Rows, Cols),
make_grid(Grid, X, Y, Vars),
nono(Rows, Cols, Grid),
label(Vars),
maplist(print_row, Grid).
@netfri25
Copy link

This is truly beautiful.
I didn't even knew that automaton existed, and now after learning your code it taught me so much and I can already see many applications of automatons!
I love it, this is so cool! thanks a lot 😁

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