I\'m trying to solve a constraint processing problem in prolog.
I need to pack 4 squares of 5x5,4x4,3x3 and 2x2 in a grid of 10x10. They may not overlap.
My
Since version 3.8.3 SICStus Prolog offers a number of dedicated placement constraints that match your packing problem nicely. In particular, as your packing problem is two-dimensional, you should consider using the disjoint2/1 constraint.
The following code snippet uses disjoint2/1 to express that rectangles are non-overlapping. The main relation is 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).
On to some queries! First, your initial packing problem:
?- 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] ? ...
Next, let's minimize the total area that is required for placing all squares:
?- 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 ? ...
What do individual solutions actually look like? ImageMagick can produce nice little bitmaps...
Here's some quick-and-dirty code for dumping the proper ImageMagick command:
:- 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]).
Above code for drawWithIM_at_area_name_label/5 relies on two little helpers:
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(_,_,_).
Let's use the following two queries to produce some still images.
?- 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').
Let's use the following hack-query to produce an image for each solution of the placement of above rectangles on a board of size 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.
Next, execute all ImageMagick commands output by above queries.
At last, build an animation of the solution set of the third query using 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
First, one solution for board size 10*10: 
Second, one solution for a board of minimum size (9*7): 
Last, all solutions for a board of minimum size (9*7): 
Since version 7.1.36 the SWI-Prolog clpfd library supports the constraint disjoint2/1.
Here's a sketch of an alternative implementation based on the tuples_in/2 constraint:
tuples_in/2 constraint. As a private proof-of-concept, I implemented some code following that idea; like @CapelliC in his answer, I get 169480 distinct solutions for the boxes and board-size the OP stated.
The runtime is comparable to the other clp(FD) based answers; in fact it is very competitive for small boards (10*10 and smaller), but gets a lot worse with larger board sizes.
Please acknowledge that, for the sake of decency, I refrain from posting the code:)