There are already several great solutions posted here (+1 for all!), using CLP(FD) constraints.
In addition, I would like to show one conceptually different way to solve such placement and covering tasks, using CLP(B) constraints.
The idea is to consider each possible placement of a tile as a set of TRUE values at specific elements on the grid, where each grid element corresponds to one column of a matrix, and each possible placement of a tile corresponds to one row. The task is then to select a set of rows of said matrix in such a way that each grid element is covered at most once, or in other words, there is at most one TRUE value in each column of the submatrix consisting of the selected rows.
In this formulation, the selection of rows — and hence the placement of tiles at specific positions — is indicated by Boolean variables, one for each row of the matrix.
Here is the code I would like to share, it works in SICStus Prolog and SWI with at most small changes:
:- use_module(library(clpb)).
:- use_module(library(clpfd)).
/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
The tiles we have available for placement.
For example, a 2x2 tile is represented in matrix form as:
[[1,1],
[1,1]]
1 indicates which grid elements are covered when placing the tile.
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
tile(5*5).
tile(4*4).
tile(3*3).
tile(2*2).
tile_matrix(Rows) :-
tile(M*N),
length(Rows, M),
maplist(length_list(N), Rows),
append(Rows, Ls),
maplist(=(1), Ls).
length_list(L, Ls) :- length(Ls, L).
/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
Describe placement of tiles as SAT constraints.
Notice the use of Cards1 to make sure that each tile is used
exactly once. Remove or change this constraint if a shape can be
used multiple times, or can even be omitted.
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
placement(M, N, Vs, *(Cs) * *(Cards1)) :-
matrix(M, N, TilesRows),
pairs_keys_values(TilesRows, Tiles, Rows),
same_length(Rows, Vs),
pairs_keys_values(TilesVs0, Tiles, Vs),
keysort(TilesVs0, TilesVs),
group_pairs_by_key(TilesVs, Groups),
pairs_values(Groups, SameTiles),
maplist(card1, SameTiles, Cards1),
Rows = [First|_],
phrase(all_cardinalities(First, Vs, Rows), Cs).
card1(Vs, card([1], Vs)).
all_cardinalities([], _, _) --> [].
all_cardinalities([_|Rest], Vs, Rows0) -->
{ maplist(list_first_rest, Rows0, Fs, Rows),
pairs_keys_values(Pairs0, Fs, Vs),
include(key_one, Pairs0, Pairs),
pairs_values(Pairs, Cs) },
[card([0,1], Cs)],
all_cardinalities(Rest, Vs, Rows).
key_one(1-_).
list_first_rest([L|Ls], L, Ls).
/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
We build a matrix M_ij, where each row i describes what placing a
tile at a specific position looks like: Each cell of the grid
corresponds to a unique column of the matrix, and the matrix
entries that are 1 indicate the grid positions that are covered by
placing one of the tiles at the described position. Therefore,
placing all tiles corresponds to selecting specific rows of the
matrix such that, for the selected rows, at most one "1" occurs in
each column.
We represent each row of the matrix as Ts-Ls, where Ts is the tile
that is used in each case.
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
matrix(M, N, Ms) :-
Squares #= M*N,
length(Ls, Squares),
findall(Ts-Ls, line(N, Ts, Ls), Ms).
line(N, Ts, Ls) :-
tile_matrix(Ts),
length(Ls, Max),
phrase((zeros(0,P0),tile_(Ts,N,Max,P0,P1),zeros(P1,_)), Ls).
tile_([], _, _, P, P) --> [].
tile_([T|Ts], N, Max, P0, P) -->
tile_part(T, N, P0, P1),
{ (P1 - 1) mod N >= P0 mod N,
P2 #= min(P0 + N, Max) },
zeros(P1, P2),
tile_(Ts, N, Max, P2, P).
tile_part([], _, P, P) --> [].
tile_part([L|Ls], N, P0, P) --> [L],
{ P1 #= P0 + 1 },
tile_part(Ls, N, P1, P).
zeros(P, P) --> [].
zeros(P0, P) --> [0], { P1 #= P0 + 1 }, zeros(P1, P).
The following query illustrates which grid elements are covered (1
), where each row corresponds to the placement of one of the rectangles:
?- M = 7, N = 9, placement(M, N, Vs, Sat), sat(Sat),
labeling(Vs), matrix(M, N, Ms), pairs_values(Ms, Rows),
pairs_keys_values(Pairs0, Vs, Rows),
include(key_one, Pairs0, Pairs1), pairs_values(Pairs1, Covers),
maplist(writeln, Covers).
[0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,1,1,1,1,1,0,0,0,0,1,1,1,1,1,0,0,0,0,1,1,1,1,1,0,0,0,0,1,1,1,1,1,0,0,0,0,1,1,1,1,1,0,0,0,0]
[0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,1,1,1,1,0,0,0,0,0,1,1,1,1,0,0,0,0,0,1,1,1,1,0,0,0,0,0,1,1,1,1]
[0,0,0,0,0,0,1,1,1,0,0,0,0,0,0,1,1,1,0,0,0,0,0,0,1,1,1,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0]
[0,0,0,0,1,1,0,0,0,0,0,0,0,1,1,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0]
M = 7,
N = 9,
etc.
corresponding to the solution:
Such a CLP(B) formulation is typically less scalable than a CLP(FD) version, also because there are more variables involved. However, it also has a few advantages:
One significant advantage is that it is readily generalized to a version of the task where some or all of the shapes can be used multiple times. For example, in the version above, we can simply change card1/2
to:
custom_cardinality(Vs, card([0,1,2,3,4,5,6,7], Vs)).
and obtain a version where each tile can be used up to 7 times, and can even be omitted entirely (due to the inclusion of 0
).
Second, we can easily turn this into a solution for an exact cover problem, which means that each grid element is covered by one of the shapes, by simple changing card([0,1], Cs)
to card([1], Cs)
in all_cardinalities//3
.
Together with the other modification, here is a covering for a 4x4 grid using four 2x2 rectangles:
[1,1,0,0,1,1,0,0,0,0,0,0,0,0,0,0]
[0,0,1,1,0,0,1,1,0,0,0,0,0,0,0,0]
[0,0,0,0,0,0,0,0,1,1,0,0,1,1,0,0]
[0,0,0,0,0,0,0,0,0,0,1,1,0,0,1,1]
A third advantage of the CLP(B) formulation is that the number of solutions can be computed without enumerating the solutions explicitly. For example, for the original task:
?- placement(7, 9, Vs, Sat), sat_count(Sat, Count).
Count = 68.
These 68 solutions are already beautifully illustrated by @repeat.
For comparison, here is the number of solutions where each shape can be used between 0 and 7 times:
?- placement(7, 9, Vs, Sat), time(sat_count(Sat, Count)).
% 157,970,727 inferences, 19.165 CPU in 19.571 seconds
...
Count = 17548478.
The same on a 10x10 grid, computed in about 6 minutes (~ 2 billion inferences):
?- placement(10, 10, Vs, Sat), sat_count(Sat, Count).
Count = 140547294509.
And on an 11x11 grid, computed in about half an hour (~ 9 billion inferences):
?- placement(11, 11, Vs, Sat), sat_count(Sat, Count).
Count = 15339263199580.
Lastly, and maybe most significantly, this approach works for any shape of tiles, and is not limited to squares or rectangles. For example, to handle 1x1 squares and a triangle shape as well as its vertical and horizontal reflections, use the following definition of tile_matrix/1
:
tile_matrix([[1]]).
tile_matrix(T) :-
T0 = [[1,1,1,1],
[1,1,1,0],
[1,1,0,0],
[1,0,0,0]],
( T = T0
; maplist(reverse, T0, T)
; reverse(T0, T)
).
Allowing each of these shapes to be used between 0 and 7 times on a 9x7 board, I get, after a minute or so, Count = 58665048314
solutions.
Here is one of them, picked at random:
Picking solutions in such a way that each of them is equally likely is also quite easy with CLP(B), even if the number of solutions is too large to enumerate them explicitly.