Sve*_*ven 36 constraints prolog sicstus-prolog clpfd clpb
我正在尝试解决prolog中的约束处理问题.
我需要在10x10的网格中打包4个5x5,4x4,3x3和2x2的正方形.它们可能不重叠.
我的变量看起来像这样:
Name: SqX(i), i=1..10, domain: 1..10
Run Code Online (Sandbox Code Playgroud)
其中X是5,4,3或2.索引i表示行,域表示网格中的列.
我的第一个约束试图定义正方形的宽度和高度.我这样制定它:
Constraint: SqX(i) > SqX(j)-X /\ i>j-X, range: i>0 /\ j>0
Run Code Online (Sandbox Code Playgroud)
这样可能的点被约束在彼此的X行和列之内.然而,Prolog会停止这些约束并给出以下结果:
Adding constraint "(Sq5_I > Sq5_J-5) /\ (I>J-5)" for values:
I=1, J=1,
I=1, J=2,
I=1, J=3,
I=1, J=4,
I=1, J=5,
I=1, J=6,
=======================[ End Solutions ]=======================
Run Code Online (Sandbox Code Playgroud)
所以它停在那里,甚至没有检查其他方块.我的约束很可能太紧张,但我不明白为什么或如何.有什么建议?
twi*_*rer 18
对于每个方块,定义X和Y表示左上角的变量.这些变量将具有域1..10-L,其中L是正方形的长度.如果将域设置为1..10,则方块可能部分位于10x10矩形之外.
然后,您可以为每对矩形发布约束,(X,Y)并(X1,Y1)声明如果它们在x轴上重叠,则它们不能在y轴上重叠,反之亦然:
(((X #=< X1) and (X+L #> X1)) => ((Y+L #=< Y1) or (Y1+L1 #=< Y))),
(((X1 #=< X) and (X1+L1 #> X)) => ((Y+L #=< Y1) or (Y1+L1 #=< Y))),
(((Y #=< Y1) and (Y+L #> Y1)) => ((X+L #=< X1) or (X1+L1 #=< X))),
(((Y1 #=< Y) and (Y1+L1 #> Y)) => ((X+L #=< X1) or (X1+L1 #=< X)))
Run Code Online (Sandbox Code Playgroud)
(您的特定约束语法可能有所不同)
rep*_*eat 18
从版本3.8.3开始,SICStus Prolog提供了许多专用的放置约束,可以很好地满足您的包装问题.特别是,由于您的包装问题是二维的,您应该考虑使用disjoint2/1约束.
以下代码段用于disjoint2/1表示矩形不重叠.主要关系是area_boxes_positions_/4.
:- use_module(library(clpfd)).
:- use_module(library(lists)).
area_box_pos_combined(W_total*H_total,W*H,X+Y,f(X,W,Y,H)) :-
X #>= 1,
X #=< W_total-W+1,
Y #>= 1,
Y #=< H_total-H+1.
positions_vars([],[]).
positions_vars([X+Y|XYs],[X,Y|Zs]) :-
positions_vars(XYs,Zs).
area_boxes_positions_(Area,Bs,Ps,Zs) :-
maplist(area_box_pos_combined(Area),Bs,Ps,Cs),
disjoint2(Cs),
positions_vars(Ps,Zs).
Run Code Online (Sandbox Code Playgroud)
对一些问题!首先,您的初始包装问题:
?- area_boxes_positions_(10*10,[5*5,4*4,3*3,2*2],Positions,Zs),
labeling([],Zs).
Positions = [1+1,1+6,5+6,5+9],
Zs = [1,1,1,6,5,6,5,9] ? ...
Run Code Online (Sandbox Code Playgroud)
接下来,让我们最小化放置所有方块所需的总面积:
?- domain([W,H],1,10),
area_boxes_positions_(W*H,[5*5,4*4,3*3,2*2],Positions,Zs),
WH #= W*H,
minimize(labeling([ff],[H,W|Zs]),WH).
W = 9,
H = 7,
Positions = [1+1,6+1,6+5,1+6],
Zs = [1,1,6,1,6,5,1,6],
WH = 63 ? ...
Run Code Online (Sandbox Code Playgroud)
个别解决方案实际上是什么样的? ImageMagick可以生成漂亮的小位图......
这里有一些用于转储正确的ImageMagick命令的快速和脏代码:
:- use_module(library(between)).
:- use_module(library(codesio)).
drawWithIM_at_area_name_label(Sizes,Positions,W*H,Name,Label) :-
Pix = 20,
% let the ImageMagick command string begin
format('convert -size ~dx~d xc:skyblue', [(W+2)*Pix, (H+2)*Pix]),
% fill canvas
format(' -stroke none -draw "fill darkgrey rectangle ~d,~d ~d,~d"',
[Pix,Pix, (W+1)*Pix-1,(H+1)*Pix-1]),
% draw grid
drawGridWithIM_area_pix("stroke-dasharray 1 1",W*H,Pix),
% draw boxes
drawBoxesWithIM_at_pix(Sizes,Positions,Pix),
% print label
write( ' -stroke none -fill black'),
write( ' -gravity southwest -pointsize 16 -annotate +4+0'),
format(' "~s"',[Label]),
% specify filename
format(' ~s~n',[Name]).
Run Code Online (Sandbox Code Playgroud)
上面的代码drawWithIM_at_area_name_label/5依赖于两个小助手:
drawGridWithIM_area_pix(Stroke,W*H,P) :- % vertical lines
write(' -strokewidth 1 -fill none -stroke gray'),
between(2,W,X),
format(' -draw "~s path \'M ~d,~d L ~d,~d\'"', [Stroke,X*P,P, X*P,(H+1)*P-1]),
false.
drawGridWithIM_area_pix(Stroke,W*H,P) :- % horizontal lines
between(2,H,Y),
format(' -draw "~s path \'M ~d,~d L ~d,~d\'"', [Stroke,P,Y*P, (W+1)*P-1,Y*P]),
false.
drawGridWithIM_area_pix(_,_,_).
drawBoxesWithIM_at_pix(Sizes,Positions,P) :-
Colors = ["#ff0000","#00ff00","#0000ff","#ffff00","#ff00ff","#00ffff"],
write(' -strokewidth 2 -stroke white'),
nth1(N,Positions,Xb+Yb),
nth1(N,Sizes, Wb*Hb),
nth1(N,Colors, Color),
format(' -draw "fill ~sb0 roundrectangle ~d,~d ~d,~d ~d,~d"',
[Color, Xb*P+3,Yb*P+3, (Xb+Wb)*P-3,(Yb+Hb)*P-3, P/2,P/2]),
false.
drawBoxesWithIM_at_pix(_,_,_).
Run Code Online (Sandbox Code Playgroud)
让我们使用以下两个查询来生成一些静态图像.
?- drawWithIM_at_area_name_label([5*5,4*4,3*3,2*2],[1+1,6+1,6+5,1+6],9*7,
'dj2_9x7.gif','9x7').
?- drawWithIM_at_area_name_label([5*5,4*4,3*3,2*2],[1+1,1+6,5+6,5+9],10*10,
'dj2_10x10.gif','10x10').
Run Code Online (Sandbox Code Playgroud)
让我们使用以下hack-query为大小板上面的矩形放置的每个解决方案生成一个图像9*7:
?- retractall(nSols(_)),
assert(nSols(1)),
W=9,H=7,
Boxes = [5*5,4*4,3*3,2*2],
area_boxes_positions_(W*H,Boxes,Positions,Zs),
labeling([],Zs),
nSols(N),
retract(nSols(_)),
format_to_codes('dj2_~5d.gif',[N],Name),
format_to_codes('~dx~d: solution #~d',[W,H,N],Label),
drawWithIM_at_area_name_label(Boxes,Positions,W*H,Name,Label),
N1 is N+1,
assert(nSols(N1)),
false.
Run Code Online (Sandbox Code Playgroud)
接下来,执行上述查询输出的所有ImageMagick命令.
最后,使用ImageMagick构建第三个查询的解集的动画:
$ convert -delay 15 dj2_0.*.gif dj2_9x7_allSolutions_1way.gif
$ convert dj2_9x7_allSolutions_1way.gif -coalesce -duplicate 1,-2-1 \
-quiet -layers OptimizePlus -loop 0 dj2_9x7_allSolutions.gif
Run Code Online (Sandbox Code Playgroud)
首先,板尺寸为10*10的一种解决方案: 
第二,最小尺寸(9*7)板的一种解决方案: 
最后,所有最小尺寸(9*7)板的解决方案: 
从版本7.1.36开始,SWI-Prolog clpfd库支持约束disjoint2/1.
以下是基于tuples_in/2约束的替代实现的草图:
tuples_in/2约束.作为一个私人的概念验证,我按照这个想法实现了一些代码; 像@CapelliC在他的回答中,我得到169480了OP所说的盒子和板尺寸的独特解决方案.
运行时与其他基于clp(FD)的答案相当; 实际上它对于小型电路板(10*10和更小)非常有竞争力,但是对于更大的电路板尺寸会变得更糟.
请注意,为了体面,我不发布代码:)
使用CLP(FD)约束,这里已经发布了几种出色的解决方案(全部为+1!)。
另外,我想展示一种使用CLP(B)约束来解决此类放置和覆盖任务的概念上不同的方法。
想法是将图块的每种可能放置都视为网格上特定元素上的一组TRUE值,其中每个网格元素对应于矩阵的一列,而图块的每种可能放置均对应于一行。然后,任务是选择所述矩阵的一组行,以使每个网格元素最多被覆盖一次,换句话说,子矩阵的每一列中最多包含一个TRUE值,该值由所选行组成。
在这种表述中,行的选择(以及因此将瓷砖放置在特定位置)由布尔变量表示,矩阵的每一行一个。
这是我想分享的代码,它可以在SICStus Prolog和SWI中工作,但只需很小的改动即可:
:- 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).
Run Code Online (Sandbox Code Playgroud)
以下查询说明了覆盖了哪些网格元素(1),其中每一行对应于一个矩形的位置:
?- 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.
Run Code Online (Sandbox Code Playgroud)
对应的解决方案:

这样的CLP(B)公式通常比CLP(FD)版本的可伸缩性差,这还因为涉及更多变量。但是,它也有一些优点:
一个重要的优点是可以很容易地将其概括为一种任务的版本,其中某些或所有形状可以多次使用。例如,在上述版本中,我们可以简单地更改card1/2为:
custom_cardinality(Vs, card([0,1,2,3,4,5,6,7], Vs)).
Run Code Online (Sandbox Code Playgroud)
并获得一个版本,其中每个图块最多可以使用7次,甚至可以完全省略(由于包含0)。
其次,我们可以轻松地将其变成精确覆盖问题的解决方案,这意味着只需将in 更改为,每个网格元素就可以被其中一种形状覆盖。card([0,1], Cs)card([1], Cs)all_cardinalities//3
与其他修改一起,这是使用四个2x2矩形的4x4网格的覆盖:
[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]
Run Code Online (Sandbox Code Playgroud)
CLP(B)公式的第三个优点是可以计算解决方案的数量,而无需明确枚举解决方案。例如,对于原始任务:
?- placement(7, 9, Vs, Sat), sat_count(Sat, Count).
Count = 68.
Run Code Online (Sandbox Code Playgroud)
@repeat已经很好地说明了这68个解决方案。
为了进行比较,以下是每种形状可以使用0到7次的解决方案数量:
?- placement(7, 9, Vs, Sat), time(sat_count(Sat, Count)).
% 157,970,727 inferences, 19.165 CPU in 19.571 seconds
...
Count = 17548478.
Run Code Online (Sandbox Code Playgroud)
在10x10的网格上也是如此,大约需要6分钟(大约20亿次推断):
?- placement(10, 10, Vs, Sat), sat_count(Sat, Count).
Count = 140547294509.
Run Code Online (Sandbox Code Playgroud)
在一个11x11的网格上,大约需要半小时的时间(大约90亿次推算):
?- placement(11, 11, Vs, Sat), sat_count(Sat, Count).
Count = 15339263199580.
Run Code Online (Sandbox Code Playgroud)
最后,也许也是最重要的一点,这种方法适用于任何形状的瓷砖,并且不仅限于正方形或矩形。例如,要处理1x1正方形和三角形以及其垂直和水平反射,请使用以下定义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)
).
Run Code Online (Sandbox Code Playgroud)
允许在9x7的板上将这些形状中的每个形状使用0至7次,大约一分钟后,我便得到了Count = 58665048314解决方案。
这是其中之一,是随机选择的:

即使解决方案的数量太大而无法明确枚举它们,使用CLP(B)也可以很容易地选择一种解决方案,使得每个解决方案具有同等的可能性。