I have tried to solve the 'Escape from Zurg' problem with clpfd. https://web.engr.oregonstate.edu/~erwig/papers/Zurg_JFP04.pdf
Toys start on the left and go to the right. This is what I have:
:-use_module(library(clpfd)).
toy(buzz,5).
toy(woody,10).
toy(res,20).
toy(hamm,25).
%two toys cross, the time is the max of the two.
cross([A,B],Time):-
toy(A,T1),
toy(B,T2),
dif(A,B),
Time#=max(T1,T2).
%one toy crosses
cross(A,T):-
toy(A,T).
%Two toys travel left to right
solve_L(Left,Right,[l_r(A,B,T)|Moves]):-
select(A,Left,L1),
select(B,L1,Left2),
cross([A,B],T),
solve_R(Left2,[A,B|Right],Moves).
%One toy has to return with the flash light
solve_R([],_,[]).
solve_R(Left,Right,[r_l(A,empty,T)|Moves]):-
select(A,Right,Right1),
cross(A,T),
solve_L([A|Left],Right1,Moves).
solve(Moves,Time):-
findall(Toy,toy(Toy,_),Toys),
solve_L(Toys,_,Moves),
all_times(Moves,Times),
sum(Times,#=,Time).
all_times([],[]).
all_times(Moves,[Time|Times]):-
Moves=[H|Tail],
H=..[_,_,_,Time],
all_times(Tail,Times).
Querying ?-solve(M,T) or ?-solve(Moves,T), labeling([min(T)],[T]). I get a solution but not one =< 60. (I cant see one either..)
How would I do this with clpfd? Or is it best to use the method in the link?
FYI: I have also found this http://www.metalevel.at/zurg/zurg.html
Which has a DCG solution. In it the constraint Time=<60 is built in, it does not find the lowest time.
Here is a CLP(FD) version, based on the code you linked to.
The main difference is that in this version, Limit is a parameter instead of a hardcoded value. In addition, it also uses the flexibility of CLP(FD) constraints to show that, compared to low-level arithmetic, you can much more freely reorder your goals when using constraints, and reason about your code much more declaratively:
:- use_module(library(clpfd)).
toy_time(buzz, 5).
toy_time(woody, 10).
toy_time(rex, 20).
toy_time(hamm, 25).
moves(Ms, Limit) :-
phrase(moves(state(0,[buzz,woody,rex,hamm],[]), Limit), Ms).
moves(state(T0,Ls0,Rs0), Limit) -->
[left_to_right(Toy1,Toy2)],
{ T1 #= T0 + max(Time1,Time2), T1 #=< Limit,
select(Toy1, Ls0, Ls1), select(Toy2, Ls1, Ls2),
Toy1 #< Toy2,
toy_time(Toy1, Time1), toy_time(Toy2, Time2) },
moves_(state(T1,Ls2,[Toy1,Toy2|Rs0]), Limit).
moves_(state(_,[],_), _) --> [].
moves_(state(T0,Ls0,Rs0), Limit) -->
[right_to_left(Toy)],
{ T1 #= T0 + Time, T1 #=< Limit,
select(Toy, Rs0, Rs1),
toy_time(Toy, Time) },
moves(state(T1,[Toy|Ls0],Rs1), Limit).
Usage example, using iterative deepening to find fastest solutions first:
?- length(_, Limit), moves(Ms, Limit).
Limit = 60,
Ms = [left_to_right(buzz, woody), right_to_left(buzz), left_to_right(hamm, rex), right_to_left(woody), left_to_right(buzz, woody)] ;
Limit = 60,
Ms = [left_to_right(buzz, woody), right_to_left(woody), left_to_right(hamm, rex), right_to_left(buzz), left_to_right(buzz, woody)] ;
Limit = 61,
Ms = [left_to_right(buzz, woody), right_to_left(buzz), left_to_right(hamm, rex), right_to_left(woody), left_to_right(buzz, woody)] ;
etc.
Note that this version uses a combination of CLP(FD) constraints (for pruning and arithmetic) and built-in Prolog backtracking, and such a combination is perfectly legitimate. In some cases, global constraints (like automaton/8 mentioned by CapelliC) can express a problem in its entirety, but combining constraints with normal backtracking is a good strategy too for many tasks.
In fact, just posting CLP(FD) constraints is typically not enough anyways: You typically also need a (backtracking) search, provided by labeling/2 in the case of CLP(FD), to obtain concrete solutions. So, this iterative deepening is similar to the search that labeling/2 would otherwise perform if you succeed to express the problem deterministically with CLP(FD) constraints alone.
Nicely, we can also show:
?- Limit #< 60, moves(Ms, Limit).
false.
EDIT: Since the thirst for automaton/8 seems to be almost unquenchable among interested users of CLP(FD) constraints, which is nice, I have also created a solution with this powerful global constraint for you. If you find this interesting, please also upvote #CapelliC's answer, since he had the initial idea to use automaton/8 for this. The idea is to let each possible (and sensible) movement of either one or two toys correspond to a unique integer, and these movements induce transitions between different states of the automaton. Notice that the side of the flash light also plays an important role in states. In addition, we equip each arc with an arithmetic expression to keep track of the time taken so far. Please try out ?- arc(_, As). to see the arcs of this automaton.
:- use_module(library(clpfd)).
toy_time(b, 5).
toy_time(w, 10).
toy_time(r, 20).
toy_time(h, 25).
toys(Toys) :- setof(Toy, T^toy_time(Toy, T), Toys).
arc0(arc0(S0,M,S)) :-
state(S0),
state0_movement_state(S0, M, S).
arcs(V, Arcs) :-
findall(Arc0, arc0(Arc0), Arcs0),
movements(Ms),
maplist(arc0_arc(V, Ms), Arcs0, Arcs).
arc0_arc(C, Ms, arc0(S0,M,S), arc(S0, MI, S, [C+T])) :-
movement_time(M, T),
nth0(MI, Ms, M).
movement_time(left_to_right(Toy), Time) :- toy_time(Toy, Time).
movement_time(left_to_right(T1,T2), Time) :-
Time #= max(Time1,Time2),
toy_time(T1, Time1),
toy_time(T2, Time2).
movement_time(right_to_left(Toy), Time) :- toy_time(Toy, Time).
state0_movement_state(lrf(Ls0,Rs0,left), left_to_right(T), lrf(Ls,Rs,right)) :-
select(T, Ls0, Ls),
sort([T|Rs0], Rs).
state0_movement_state(lrf(Ls0,Rs0,left), left_to_right(T1,T2), S) :-
state0_movement_state(lrf(Ls0,Rs0,left), left_to_right(T1), lrf(Ls1,Rs1,_)),
state0_movement_state(lrf(Ls1,Rs1,left), left_to_right(T2), S),
T1 #< T2.
state0_movement_state(lrf(Ls0,Rs0,right), right_to_left(T), lrf(Ls,Rs,left)) :-
select(T, Rs0, Rs),
sort([T|Ls0], Ls).
movements(Moves) :-
toys(Toys),
findall(Move, movement(Toys, Move), Moves).
movement(Toys, Move) :-
member(T, Toys),
( Move = left_to_right(T)
; Move = right_to_left(T)
).
movement(Toys0, left_to_right(T1, T2)) :-
select(T1, Toys0, Toys1),
member(T2, Toys1),
T1 #< T2.
state(lrf(Lefts,Rights,Flash)) :-
toys(Toys),
phrase(lefts(Toys), Lefts),
foldl(select, Lefts, Toys, Rights),
( Flash = left ; Flash = right ).
lefts([]) --> [].
lefts([T|Ts]) --> ( [T] | [] ), lefts(Ts).
And now, at long last, we can finally use automaton/8 which we so deeply desire for a solution we truly deem worthy of carrying the "CLP(FD)" banner, orgiastically mixed with the min/1 option of labeling/2:
?- time((arcs(C, Arcs),
length(Vs, _),
automaton(Vs, _, Vs, [source(lrf([b,h,r,w],[],left)),
sink(lrf([],[b,h,r,w],right))],
Arcs, [C], [0], [Time]),
labeling([min(Time)], Vs))).
yielding:
857,542 inferences, 0.097 CPU in 0.097 seconds(100% CPU, 8848097 Lips)
Arcs = [...],
Time = 60,
Vs = [10, 1, 11, 7, 10] ;
etc.
I leave translating such solutions to readable state transitions as an easy exercise (~3 lines of code).
For extra satisfaction, this is much faster than the original version with plain Prolog, for which we had:
?- time((length(_, Limit), moves(Ms, Limit))).
1,666,522 inferences, 0.170 CPU in 0.170 seconds (100% CPU, 9812728 Lips)
The moral of this story: If your straight-forward Prolog solution takes more than a tenth of a second to yield solutions, you better learn how to use one of the most complex and powerful global constraints in order to improve the running time by a few milliseconds! :-)
On a more serious note though, this example shows that constraint propagation can pay off very soon, even for comparatively small search spaces. You can expect even larger relative gains when solving more complex search problems with CLP(FD).
Note though that the second version, although it propagates constraints more globally in a sense, lacks an important feature that is also related to propagation and pruning: Previously, we were able to directly use the program to show that there is no solution that takes less than 60 minutes, using a straight-forward and natural query (?- Limit #< 60, moves(Ms, Limit)., which failed). This follows from the second program only implicitly, because we know that, ceteris paribus, longer lists can at most increase the time taken. Unfortunately though, the isolated call of length/2 did not get the memo.
On the other hand, the second version is able to prove something that is in a sense at least equally impressive, and it does so more efficiently and somewhat more directly than the first version: Without even constructing a single explicit solution, we can use the second version to show that any solution (if there is one) takes at least 5 crossings:
?- time((arcs(C, Arcs),
length(Vs, L),
automaton(Vs, _, Vs, [source(lrf([b,h,r,w],[],left)),
sink(lrf([],[b,h,r,w],right))],
Arcs, [C], [0], [Time]))).
yielding:
331,495 inferences, 0.040 CPU in 0.040 seconds (100% CPU, 8195513 Lips)
...,
L = 5
... .
This works by constraint propagation alone, and does not involve any labeling/2!
I think that modelling with CLPFD this puzzle could be done with automaton/8.
In Prolog I would write
escape_zurg(T,S) :-
aggregate(min(T,S), (
solve([5,10,20,25], [], S),
sum_timing(S, T)), min(T,S)).
solve([A, B], _, [max(A, B)]).
solve(L0, R0, [max(A, B), C|T]) :-
select(A, L0, L1),
select(B, L1, L2),
append([A, B], R0, R1),
select(C, R1, R2),
solve([C|L2], R2, T).
sum_timing(S, T) :-
aggregate(sum(E), member(E, S), T).
that yields this solution
?- escape_zurg(T,S).
T = 60,
S = [max(5, 10), 5, max(20, 25), 10, max(10, 5)].
edit
well, automaton/8 is well beyond my reach...
let's start simpler: what could be a simple representation of state ?
on left/right we have 4 slots, that can be empty: so
escape_clpfd(T, Sf) :-
L0 = [_,_,_,_],
Zs = [0,0,0,0],
L0 ins 5\/10\/20\/25,
all_different(L0),
...
now, since the problem it's so simple, we can 'hardcode' the state change
...
lmove(L0/Zs, 2/2, L1/R1, T1), rmove(L1/R1, 1/3, L2/R2, T2),
lmove(L2/R2, 3/1, L3/R3, T3), rmove(L3/R3, 2/2, L4/R4, T4),
lmove(L4/R4, 4/0, Zs/ _, T5),
...
the first lmove/4 must shift 2 elements from left to right, and after it have done, we will have 2 zeros at left, and 2 at right. The timing (T1) will be max(A,B), where A,B are incognite by now.
rmove/4 is similar, but will 'return' in T2 the only element (incognito) it will move from right to left. We are encoding the evolution asserting the number of 0s on each side (seems not difficult to generalize).
Let's complete:
...
T #= T1 + T2 + T3 + T4 + T5,
Sf = [T1,T2,T3,T4,T5].
Now, rmove/4 is simpler, so let's code it:
rmove(L/R, Lz/Rz, Lu/Ru, M) :-
move_one(R, L, Ru, Lu, M),
count_0s(Ru, Rz),
count_0s(Lu, Lz).
it defers to move_one/5 the actual work, then applies the numeric constraint we hardcoded above:
count_0s(L, Z) :-
maplist(is_0, L, TF),
sum(TF, #=, Z).
is_0(V, C) :- V #= 0 #<==> C.
is_0/2 reifies the empty slot condition, that is makes countable the truth value. It's worth to test it:
?- count_0s([2,1,1],X).
X = 0.
?- count_0s([2,1,C],1).
C = 0.
?- count_0s([2,1,C],2).
false.
Coding move_one/5 in CLP(FD) seems difficult. Here Prolog nondeterminism seems really appropriate...
move_one(L, R, [Z|Lt], [C|Rt], C) :-
select(C, L, Lt), is_0(C, 0),
select(Z, R, Rt), is_0(Z, 1).
select/3 it's a pure predicate, and Prolog will backtrack when labeling will need...
There is no minimization, but that is easy to add after we get the solutions.
So far, all seems 'logical' to me. But, of course...
?- escape_clpfd(T, S).
false.
So, here be dragons...
?- spy(lmove),escape_clpfd(T, S).
% Spy point on escape_zurg:lmove/4
* Call: (9) escape_zurg:lmove([_G12082{clpfd = ...}, _G12164{clpfd = ...}, _G12246{clpfd = ...}, _G12328{clpfd = ...}]/[0, 0, 0, 0], 2/2, _G12658/_G12659, _G12671) ? creep
Call: (10) escape_zurg:move_one([_G12082{clpfd = ...}, _G12164{clpfd = ...}, _G12246{clpfd = ...}, _G12328{clpfd = ...}], [0, 0, 0, 0], _G12673, _G12674, _G12661) ? sskip
... etc etc
Sorry, will post a solution if I'll get some spare time to debug...
edit there were several bugs... with this lmove/4
lmove(L/R, Lz/Rz, Lu/Ru, max(A, B)) :-
move_one(L, R, Lt, Rt, A),
move_one(Lt, Rt, Lu, Ru, B),
count_0s(Lu, Lz),
count_0s(Ru, Rz).
at least we start getting solutions (added variables to interface to label from outside...)
escape_clpfd(T, Sf, L0) :- ...
?- escape_clpfd(T, S, Vs), label(Vs).
T = 85,
S = [max(5, 10), 10, max(10, 20), 20, max(20, 25)],
Vs = [5, 10, 20, 25] ;
T = 95,
S = [max(5, 10), 10, max(10, 25), 25, max(25, 20)],
Vs = [5, 10, 25, 20] ;
...
edit
the code above works, but is painfully slow:
?- time((escape_clpfd(60, Sf, L0),label(L0))).
% 15,326,054 inferences, 5.466 CPU in 5.485 seconds (100% CPU, 2803917 Lips)
Sf = [max(5, 10), 10, max(20, 25), 5, max(5, 10)],
L0 = [5, 10, 20, 25]
with this change to move_one/5:
move_one([L|Ls], [R|Rs], [R|Ls], [L|Rs], L) :-
L #\= 0,
R #= 0.
move_one([L|Ls], [R|Rs], [L|Lu], [R|Ru], E) :-
move_one(Ls, Rs, Lu, Ru, E).
I have better performance:
?- time((escape_clpfd(60, Sf, L0),label(L0))).
% 423,394 inferences, 0.156 CPU in 0.160 seconds (97% CPU, 2706901 Lips)
Sf = [max(5, 10), 5, max(20, 25), 10, max(5, 10)],
L0 = [5, 10, 20, 25]
then, adding to lmove/4
... A #< B, ...
i get
% 233,953 inferences, 0.089 CPU in 0.095 seconds (94% CPU, 2621347 Lips)
Sf = [max(5, 10), 5, max(20, 25), 10, max(5, 10)],
the whole it's still a lot slower than my pure Prolog solution...
edit
other small improvements:
?- time((escape_clpfd(60, Sf, L0),maplist(#=,L0,[5,10,20,25]))).
% 56,583 inferences, 0.020 CPU in 0.020 seconds (100% CPU, 2901571 Lips)
Sf = [max(5, 10), 5, max(20, 25), 10, max(5, 10)],
where all_different/1 has been replaced by
...
chain(L0, #<),
...
Another improvement: counting both side for zeros is useless: removing (arbitrarly) one side in both lmove and rmove we get
% 35,513 inferences, 0.014 CPU in 0.014 seconds (100% CPU, 2629154 Lips)
Sf = [max(5, 10), 5, max(20, 25), 10, max(5, 10)],
edit
Just for fun, here is the same pure (except aggregation) Prolog solution, using a simple deterministic 'lifting' of variables (courtesy 'lifter'):
:- use_module(carlo(snippets/lifter)).
solve([A, B], _, [max(A, B)]).
solve(L0, R0, [max(A, B), C|T]) :-
solve([C|select(B, select(A, L0, °), °)],
select(C, append([A, B], R0, °), °),
T).
btw, it's rather fast:
?- time(escape_zurg(T,S)).
% 50,285 inferences, 0.065 CPU in 0.065 seconds (100% CPU, 769223 Lips)
T = 60,
S = [max(5, 10), 5, max(20, 25), 10, max(10, 5)].
(the absolute timing is not so good because I'm running a SWI-Prolog compiled for debugging)
I think #mat has come up with a good answer for what I was originally trying to do but I did try and also use automaton/4, alongside backtracking search to add arcs. This is as far I got. But I get the error ERROR: Arguments are not sufficiently instantiated when calling bridge/2. Just posting here if anyone has any comments on this approach or knows why this would come up with this error, or if I am using automaton/4 completely wrong!
fd_length(L, N) :-
N #>= 0,
fd_length(L, N, 0).
fd_length([], N, N0) :-
N #= N0.
fd_length([_|L], N, N0) :-
N1 is N0+1,
N #>= N1,
fd_length(L, N, N1).
left_to_right_arc(L0,R0,Arc):-
LenL#=<4,
fd_length(L0,LenL),
LenR #=4-LenL,
fd_length(R0,LenR),
L0 ins 5\/10\/20\/25,
R0 ins 5\/10\/20\/25,
append(L0,R0,All),
all_different(All),
Before =[L0,R0],
select(A,L0,L1),
select(B,L1,L2),
append([A,B],R0,R1),
After=[L2,R1],
Cost #=max(A,B),
Arc =arc(Before,Cost,After).
right_to_left_arc(L0,R0,Arc):-
LenL#=<4,
fd_length(L0,LenL),
LenR #=4-LenL,
fd_length(R0,LenR),
L0 ins 5\/10\/20\/25,
R0 ins 5\/10\/20\/25,
append(L0,R0,All),
all_different(All),
Before=[L0,R0],
select(A,R0,R1),
append([A],L0,L1),
After=[L1,R1],
Cost#=A,
Arc =arc(After,Cost,Before).
pair_of_arcs(Arcs):-
left_to_right_arc(_,_,ArcLR),
right_to_left_arc(_,_,ArcRL),
Arcs =[ArcLR,ArcRL].
pairs_of_arcs(Pairs):-
L#>=1,
fd_length(Pairs,L),
once(maplist(pair_of_arcs,Pairs)).
bridge(Vs,Arcs):-
pairs_of_arcs(Arcs),
flatten(Arcs,FArcs),
automaton(Vs,[source([[5,10,20,25],[]]),sink([[],[5,10,20,25]])],
FArcs).
This is not an answer for using CLP(FD) but just to show the two solutions that exist for this puzzle with cost equal or lower than 60 (the text is too big to put in a comment).
There are several variations of this puzzle. Logtalk includes one, in its searching/bridge.lgt example, with different set of characters and corresponding times to cross the bridge. But we can patch it to solve instead for the variation in this question (using the current Logtalk git version):
?- set_logtalk_flag(complements, allow).
true.
?- {searching(loader)}.
...
% (0 warnings)
true.
?- create_category(patch, [complements(bridge)], [], [initial_state(start, ([5,10,20,25], left, [])), goal_state(end, ([], right, [5,10,20,25]))]).
true.
?- performance::init, bridge::initial_state(Initial), hill_climbing(60)::solve(bridge, Initial, Path, Cost), bridge::print_path(Path), performance::report.
5 10 20 25 lamp _|____________|_
20 25 _|____________|_ lamp 5 10
5 20 25 lamp _|____________|_ 10
5 _|____________|_ lamp 10 20 25
5 10 lamp _|____________|_ 20 25
_|____________|_ lamp 5 10 20 25
solution length: 6
state transitions (including previous solutions): 113
ratio solution length / state transitions: 0.05309734513274336
minimum branching degree: 1
average branching degree: 5.304347826086956
maximum branching degree: 10
time: 0.004001000000000032
Initial = ([5, 10, 20, 25], left, []),
Path = [([5, 10, 20, 25], left, []), ([20, 25], right, [5, 10]), ([5, 20, 25], left, [10]), ([5], right, [10, 20, 25]), ([5, 10], left, [20, 25]), ([], right, [5|...])],
Cost = 60 ;
5 10 20 25 lamp _|____________|_
20 25 _|____________|_ lamp 5 10
10 20 25 lamp _|____________|_ 5
10 _|____________|_ lamp 5 20 25
5 10 lamp _|____________|_ 20 25
_|____________|_ lamp 5 10 20 25
solution length: 6
state transitions (including previous solutions): 219
ratio solution length / state transitions: 0.0273972602739726
minimum branching degree: 1
average branching degree: 5.764705882352941
maximum branching degree: 10
time: 0.0038759999999999906
Initial = ([5, 10, 20, 25], left, []),
Path = [([5, 10, 20, 25], left, []), ([20, 25], right, [5, 10]), ([10, 20, 25], left, [5]), ([10], right, [5, 20, 25]), ([5, 10], left, [20, 25]), ([], right, [5|...])],
Cost = 60 ;
false.
Related
I wonder if there is a way to solve a knapsack problem in CLP(B).
CLP(B) seems to be suitable, since packing an item can be modelled as a Boolean variable.
Example:
x1,x2,x3,x4,x5 e {0,1}
x1*12+x2*2+x3*1+x4*1+x5*4 =< 15
maximize x1*4+x2*2+x3*2+x4*1+x5*10
I am little bit at loss how to formulate the side condition of the limited capacity of the knappsack. It seems that SWI-Prolog has weighted_maximum/3 which would allow the optimization.
Picture from https://en.wikipedia.org/wiki/Knapsack_problem
You can model size(weight) constraints by issuing new variables to account for the weight, then use card constraint to model capacity of the backpack and finally using weighted_maximum/2 to maximize objective:
:- use_module(library(clpb)).
knapsack_sample([X1,X2,X3,X4,X5], Maximum):-
knapsack([X1-12/4,X2-2/2,X3-1/2,X4-1/1,X5-4/10], 15, Maximum).
% Data is a list of BucketVar-Value/Weight
knapsack(Data, Capacity, Maximum):-
buckets(Data, [], [], Buckets, AndEqAll, Weights, Xs),
sat(card([0-Capacity], Buckets)),
sat(AndEqAll),
weighted_maximum(Weights, Xs, Maximum).
buckets([], [EqAll|LEqAll], LBuckets, Buckets, AndEqAll, [], []):-
foldl(andall, LEqAll, EqAll, AndEqAll),
append(LBuckets, Buckets).
buckets([X-Count/Weight|Counts], LEqAll, LBuckets, Buckets, AndEqAll, [Weight|Weights], [X|Xs]):-
length([B|Bs], Count),
foldl(eqall(X), Bs, (X=:=B), EqAll),
buckets(Counts, [EqAll|LEqAll], [[B|Bs]|LBuckets], Buckets, AndEqAll, Weights, Xs).
eqall(B, X, Y, (B=:=X)*Y).
andall(X, Y, X*Y).
So in your example you would call knapsack with Data=[X1-12/4,X2-2/2,X3-1/2,X4-1/1,X5-4/10] and 15 as capacity:
?- knapsack([X1-12/4,X2-2/2,X3-1/2,X4-1/1,X5-4/10], 15, Maximum).
X1 = 0,
X2 = X3, X3 = X4, X4 = X5, X5 = 1,
Maximum = 15.
UPDATE:
Actually card constraints handle repetitions fine so there's no need to add new variables, and the solution gets simpler:
knapsack2(Data, Capacity, Maximum):-
maplist(knap, Data, LBuckets, Weights, Xs),
append(LBuckets, Buckets),
sat(card([0-Capacity], Buckets)),
weighted_maximum(Weights, Xs, Maximum).
knap(X-Value/Weight, Ws, Weight, X):-
length(Ws, Value),
maplist(=(X), Ws).
Sample run:
?- knapsack2([X1-12/4,X2-2/2,X3-1/2,X4-1/1,X5-4/10], 15, Maximum).
X1 = 0,
X2 = X3, X3 = X4, X4 = X5, X5 = 1,
Maximum = 15.
I have recently added a constraint pseudo/4 in my CLP(B), similar to the constraint scalar_product/4 from CLP(FD), which will not create a circuit, but instead maintain the constraint in a more traditional way. The code reads then:
knapsack([X1,X2,X3,X4,X5], M) :-
pseudo([12,2,1,1,4], [X1,X2,X3,X4,X5], =<, 15),
weighted_maximum([4,2,2,1,10], [X1,X2,X3,X4,X5], M).
I compared with the card/2 formulation. Unlike the pseudo/4 formulation, the card/2 formulation will created a circuit under the hood. This is both the case for my system, as well as for SWI-Proilog:
knapsack3([X1,X2,X3,X4,X5], M) :-
sat(card([0-15],[X1,X1,X1,X1,X1,X1,X1,X1,X1,X1,X1,X1,X2,X2,X3,X4,X5,X5,X5,X5])),
weighted_maximum([4,2,2,1,10], [X1,X2,X3,X4,X5], M).
I did some tests, also measuring the model set-up time. The new pseudo/4 constraint seems to be the winner for this example. Here are the results in my system:
Jekejeke Prolog 3, Runtime Library 1.3.8 (May 23, 2019)
?- time((between(1,100,_), knapsack(_,_), fail; true)).
% Up 95 ms, GC 3 ms, Thread Cpu 93 ms (Current 07/05/19 20:03:05)
Yes
?- time((between(1,100,_), knapsack3(_,_), fail; true)).
% Up 229 ms, GC 5 ms, Thread Cpu 219 ms (Current 07/05/19 20:02:58)
Yes
And here is the result in SWI-Prolog:
?- time((between(1,100,_), knapsack3(_,_), fail; true)).
% 8,229,000 inferences, 0.656 CPU in 0.656 seconds (100% CPU, 12539429 Lips)
Consider the problem from https://puzzling.stackexchange.com/questions/20238/explore-the-square-with-100-hops:
Given a grid of 10x10 squares, your task is to visit every square exactly once. In each step, you may
skip 2 squares horizontally or vertically or
skip 1 square diagonally
In other words (closer to my implementation below), label a 10x10 grid with numbers from 1 to 100 such that each square at coordinates (X, Y) is 1 or is equal to one more than the "previous" square at (X, Y-3), (X, Y+3), (X-3, Y), (X+3, Y), (X-2, Y-2), (X-2, Y+2), (X+2, Y-2), or (X+2, Y+2).
This looks like a straightforward constraint programming problem, and Z3 can solve it in 30 seconds from a simple declarative specification: https://twitter.com/johnregehr/status/1070674916603822081
My implementation in SWI-Prolog using CLP(FD) does not scale quite as nicely. In fact, it cannot even solve the 5x5 instance of the problem unless almost two rows are pre-specified:
?- number_puzzle_(_Square, Vars), Vars = [1,24,14,2,25, 16,21,5,8,20 |_], time(once(labeling([], Vars))).
% 10,063,059 inferences, 1.420 CPU in 1.420 seconds (100% CPU, 7087044 Lips)
_Square = square(row(1, 24, 14, 2, 25), row(16, 21, 5, 8, 20), row(13, 10, 18, 23, 11), row(4, 7, 15, 3, 6), row(17, 22, 12, 9, 19)),
Vars = [1, 24, 14, 2, 25, 16, 21, 5, 8|...].
?- number_puzzle_(_Square, Vars), Vars = [1,24,14,2,25, 16,21,5,8,_ |_], time(once(labeling([], Vars))).
% 170,179,147 inferences, 24.152 CPU in 24.153 seconds (100% CPU, 7046177 Lips)
_Square = square(row(1, 24, 14, 2, 25), row(16, 21, 5, 8, 20), row(13, 10, 18, 23, 11), row(4, 7, 15, 3, 6), row(17, 22, 12, 9, 19)),
Vars = [1, 24, 14, 2, 25, 16, 21, 5, 8|...].
?- number_puzzle_(_Square, Vars), Vars = [1,24,14,2,25, 16,21,5,_,_ |_], time(once(labeling([], Vars))).
% 385,799,962 inferences, 54.939 CPU in 54.940 seconds (100% CPU, 7022377 Lips)
_Square = square(row(1, 24, 14, 2, 25), row(16, 21, 5, 8, 20), row(13, 10, 18, 23, 11), row(4, 7, 15, 3, 6), row(17, 22, 12, 9, 19)),
Vars = [1, 24, 14, 2, 25, 16, 21, 5, 8|...].
(This is on an oldish machine with SWI-Prolog 6.0.0. On a newer machine with SWI-Prolog 7.2.3 it runs about twice as fast, but that's not enough to beat the apparent exponential complexity.)
The partial solution used here is from https://www.nurkiewicz.com/2018/09/brute-forcing-seemingly-simple-number.html
So, my question: How can I speed up the following CLP(FD) program?
Additional question for extra thanks: Is there a specific labeling parameter that speeds up this search significantly, and if so, how could I make an educated guess at which one it might be?
:- use_module(library(clpfd)).
% width of the square board
n(5).
% set up a term square(row(...), ..., row(...))
square(Square, N) :-
length(Rows, N),
maplist(row(N), Rows),
Square =.. [square | Rows].
row(N, Row) :-
functor(Row, row, N).
% Entry is the entry at 1-based coordinates (X, Y) on the board. Fails if X
% or Y is an invalid coordinate.
square_coords_entry(Square, (X, Y), Entry) :-
n(N),
0 < Y, Y =< N,
arg(Y, Square, Row),
0 < X, X =< N,
arg(X, Row, Entry).
% Constraint is a CLP(FD) constraint term relating variable Var and the
% previous variable at coordinates (X, Y). X and Y may be arithmetic
% expressions. If X or Y is an invalid coordinate, this predicate succeeds
% with a trivially false Constraint.
square_var_coords_constraint(Square, Var, (X, Y), Constraint) :-
XValue is X,
YValue is Y,
( square_coords_entry(Square, (XValue, YValue), PrevVar)
-> Constraint = (Var #= PrevVar + 1)
; Constraint = (0 #= 1) ).
% Compute and post constraints for variable Var at coordinates (X, Y) on the
% board. The computed constraint expresses that Var is 1, or it is one more
% than a variable located three steps in one of the cardinal directions or
% two steps along a diagonal.
constrain_entry(Var, Square, X, Y) :-
square_var_coords_constraint(Square, Var, (X - 3, Y), C1),
square_var_coords_constraint(Square, Var, (X + 3, Y), C2),
square_var_coords_constraint(Square, Var, (X, Y - 3), C3),
square_var_coords_constraint(Square, Var, (X, Y + 3), C4),
square_var_coords_constraint(Square, Var, (X - 2, Y - 2), C5),
square_var_coords_constraint(Square, Var, (X + 2, Y - 2), C6),
square_var_coords_constraint(Square, Var, (X - 2, Y + 2), C7),
square_var_coords_constraint(Square, Var, (X + 2, Y + 2), C8),
Var #= 1 #\/ C1 #\/ C2 #\/ C3 #\/ C4 #\/ C5 #\/ C6 #\/ C7 #\/ C8.
% Compute and post constraints for the entire board.
constrain_square(Square) :-
n(N),
findall(I, between(1, N, I), RowIndices),
maplist(constrain_row(Square), RowIndices).
constrain_row(Square, Y) :-
arg(Y, Square, Row),
Row =.. [row | Entries],
constrain_entries(Entries, Square, 1, Y).
constrain_entries([], _Square, _X, _Y).
constrain_entries([E|Es], Square, X, Y) :-
constrain_entry(E, Square, X, Y),
X1 is X + 1,
constrain_entries(Es, Square, X1, Y).
% The core relation: Square is a puzzle board, Vars a list of all the
% entries on the board in row-major order.
number_puzzle_(Square, Vars) :-
n(N),
square(Square, N),
constrain_square(Square),
term_variables(Square, Vars),
Limit is N * N,
Vars ins 1..Limit,
all_different(Vars).
First of all:
What is going on here?
To see what is happening, here are PostScript definitions that let us visualize the search:
/n 5 def
340 n div dup scale
-0.9 0.1 translate % leave room for line strokes
/Palatino-Roman 0.8 selectfont
/coords { n exch sub translate } bind def
/num { 3 1 roll gsave coords 0.5 0.2 translate
5 string cvs dup stringwidth pop -2 div 0 moveto show
grestore } bind def
/clr { gsave coords 1 setgray 0 0 1 1 4 copy rectfill
0 setgray 0.02 setlinewidth rectstroke grestore} bind def
1 1 n { 1 1 n { 1 index clr } for pop } for
These definitions give you two procedures:
clr to clear a square
num to show a number on a square.
For example, if you save these definitions to tour.ps and then invoke the PostScript interpreter Ghostscript with:
gs -r72 -g350x350 tour.ps
and then enter the following instructions:
1 2 3 num
1 2 clr
2 3 4 num
you get:
PostScript is a great programming language for visualizing search processes, and I also recommend to check out postscript for more information.
We can easily modify your program to emit suitable PostScript instructions that let us directly observe the search. I highlight the relevant additions:
constrain_entries([], _Square, _X, _Y).
constrain_entries([E|Es], Square, X, Y) :-
freeze(E, postscript(X, Y, E)),
constrain_entry(E, Square, X, Y),
X1 #= X + 1,
constrain_entries(Es, Square, X1, Y).
postscript(X, Y, N) :- format("~w ~w ~w num\n", [X,Y,N]).
postscript(X, Y, _) :- format("~w ~w clr\n", [X,Y]), false.
I have also taken the liberty to change (is)/2 to (#=)/2 to make the program more general.
Assuming that you saved the PostScript definitions in tour.ps and your Prolog program in tour.pl, the following invocation of SWI-Prolog and Ghostscript illustrates the situation:
swipl -g "number_puzzle_(_, Vs), label(Vs)" tour.pl | gs -g350x350 -r72 tour.ps -dNOPROMPT
For example, we see a lot of backtracking at the highlighted position:
However, essential problems already lie completely elsewhere:
None of the highlighted squares are valid moves!
From this, we see that your current formulation does not—at least not sufficiently early—let the solver recognize when a partial assignment cannot be completed to a solution! This is bad news, since failure to recognize inconsistent assignments often leads to unacceptable performance. For example, in order to correct the 1 → 3 transition (which can never occur in this way, yet is already one of the first choices made in this case), the solver would have to backtrack over approximately 8 squares, after enumerating—as a very rough estimate—258 = 152587890625 partial solutions, and then start all over at only the second position in the board.
In the constraint literature, such backtracking is called thrashing. It means repeated failure due to the same reason.
How is this possible? Your model seems to be correct, and can be used to detect solutions. That's good! However, a good constraint formulation not only recognizes solutions, but also quickly detects partial assignments that cannot be completed to solutions. This is what allows the solver to effectively prune the search, and it is in this important respect that your current formulation falls short. One of the reasons for this has to do with constraint propagation in reified constraints that you are using. In particular, consider the following query:
?- (X + 1 #= 3) #<==> B, X #\= 2.
Intuitively, we expect B = 0. But that is not the case! Instead, we get:
X in inf..1\/3..sup,
X+1#=_3840,
_3840#=3#B,
B in 0..1.
So, the solver does not propagate reified equality very strongly. Maybe it should though! Only sufficient feedback from Prolog practitioners will tell whether this area of the constraint solver should be changed, possibly trading a bit of speed for stronger propagation. The high relevance of this feedback is one of the reasons why I recommend to use CLP(FD) constraints whenever you have the opportunity, i.e., every time you are reasoning about integers.
For this particular case, I can tell you that making the solver stronger in this sense does not make that much of a difference. You essentially end up with a version of the board where the core issue still arises, with many transitions (some of them highlighted below) that cannot occur in any solution:
Fixing the core issue
We should eliminate the cause of the backtracking at its core. To prune the search, we must recognize inconsistent (partial) assignments earlier.
Intuitively, we are searching for a connected tour, and want to backtrack as soon as it is clear that the tour cannot be continued in the intended way.
To accomplish what we want, we have at least two options:
change the allocation strategy to take connectedness into account
model the problem in such a way that connectedness is more strongly taken into account.
Option 1: Allocation strategy
A major attraction of CLP(FD) constraints is that they let us decouple the task description from the search. When using CLP(FD) constraints, we often perform search via label/1 or labeling/2. However, we are free to assign values to variables in any way we want. This is very easy if we follow—as you have done—the good practice of putting the "constraint posting" part into its own predicate, called the core relation.
For example, here is a custom allocation strategy that makes sure that the tour remains connected at all times:
allocation(Vs) :-
length(Vs, N),
numlist(1, N, Ns),
maplist(member_(Vs), Ns).
member_(Es, E) :- member(E, Es).
With this strategy, we get a solution for the 5×5 instance from scratch:
?- number_puzzle_(Square, Vars), time(allocation(Vars)).
% 5,030,522 inferences, 0.907 CPU in 0.913 seconds (99% CPU, 5549133 Lips)
Square = square(row(1, 8, 5, 2, 11), ...),
Vars = [1, 8, 5, 2, 11, 16, 21, 24, 15|...]
There are various modifications of this strategy that are worth trying out. For example, when multiple squares are admissible, we could try to make a more intelligent choice by taking into account the number of remaining domain elements of the squares. I leave trying such improvements as a challenge.
From the standard labeling strategies, the min labeling option is in effect quite similar to this strategy in this case, and indeed it also finds a solution for the 5×5 case:
?- number_puzzle_(Square, Vars), time(labeling([min], Vars)).
% 22,461,798 inferences, 4.142 CPU in 4.174 seconds (99% CPU, 5422765 Lips)
Square = square(row(1, 8, 5, 2, 11), ...),
Vars = [1, 8, 5, 2, 11, 16, 21, 24, 15|...] .
However, even a fitting allocation strategy cannot fully compensate weak constraint propagation. For the 10×10 instance, the board looks like this after some search with the min option:
Note that we also have to adapt the value of n in the PostScript code to visualize this as intended.
Ideally, we should formulate the task in such a way that we benefit from strong propagation, and then also use a good allocation strategy.
Option 2: Remodeling
A good CLP formulation propagates as strongly as possible (in acceptable time). We should therefore strive to use constraints that allow the solver to reason more readily about the task's most important requirements. In this concrete case, it means that we should try to find a more suitable formulation for what is currently expressed as a disjunction of reified constraints that, as shown above, do not allow much propagation. In theory, the constraint solver could recognize such patterns automatically. However, that is impractical for many use cases, and we therefore must sometimes experiment by manually trying several promising formulations. Still, also in this case: With sufficient feedback from application programmers, such cases are more likely to be improved and worked on!
I now use the CLP(FD) constraint circuit/1 to make clear that we are looking for a Hamiltonian circuit in a particular graph. The graph is expressed as a list of integer variables, where each element denotes the position of its successor in the list.
For example, a list with 3 elements admits precisely 2 Hamiltonian circuits:
?- Vs = [_,_,_], circuit(Vs), label(Vs).
Vs = [2, 3, 1] ;
Vs = [3, 1, 2].
I use circuit/1 to describe solutions that are also closed tours. This means that, if we find such a solution, then we can start again from the beginning via a valid move from the last square in the found tour:
n_tour(N, Vs) :-
L #= N*N,
length(Vs, L),
successors(Vs, N, 1),
circuit(Vs).
successors([], _, _).
successors([V|Vs], N, K0) :-
findall(Num, n_k_next(N, K0, Num), [Next|Nexts]),
foldl(num_to_dom, Nexts, Next, Dom),
V in Dom,
K1 #= K0 + 1,
successors(Vs, N, K1).
num_to_dom(N, D0, D0\/N).
n_x_y_k(N, X, Y, K) :- [X,Y] ins 1..N, K #= N*(Y-1) + X.
n_k_next(N, K, Next) :-
n_x_y_k(N, X0, Y0, K),
( [DX,DY] ins -2 \/ 2
; [DX,DY] ins -3 \/ 0 \/ 3,
abs(DX) + abs(DY) #= 3
),
[X,Y] ins 1..N,
X #= X0 + DX,
Y #= Y0 + DY,
n_x_y_k(N, X, Y, Next),
label([DX,DY]).
Note how admissible successors are now expressed as domain elements, reducing the number of constraints and entirely eliminating the need for reifications. Most importantly, the intended connectedness is now automatically taken into account and enforced at every point during the search. The predicate n_x_y_k/4 relates (X,Y) coordinates to list indices. You can easily adapt this program to other tasks (e.g., knight's tour) by changing n_k_next/3. I leave the generalization to open tours as a challenge.
Here are additional definitions that let us print solutions in a more readable form:
:- set_prolog_flag(double_quotes, chars).
print_tour(Vs) :-
length(Vs, L),
L #= N*N, N #> 0,
length(Ts, N),
tour_enumeration(Vs, N, Es),
phrase(format_string(Ts, 0, 4), Fs),
maplist(format(Fs), Es).
format_(Fs, Args, Xs0, Xs) :- format(chars(Xs0,Xs), Fs, Args).
format_string([], _, _) --> "\n".
format_string([_|Rest], N0, I) -->
{ N #= N0 + I },
"~t~w~", call(format_("~w|", [N])),
format_string(Rest, N, I).
tour_enumeration(Vs, N, Es) :-
length(Es, N),
maplist(same_length(Es), Es),
append(Es, Ls),
foldl(vs_enumeration(Vs, Ls), Vs, 1-1, _).
vs_enumeration(Vs, Ls, _, V0-E0, V-E) :-
E #= E0 + 1,
nth1(V0, Ls, E0),
nth1(V0, Vs, V).
In formulations with strong propagation, the predefined ff search strategy is often a good strategy. And indeed it lets us solve the whole task, i.e., the original 10×10 instance, within a few seconds on a commodity machine:
?- n_tour(10, Vs),
time(labeling([ff], Vs)),
print_tour(Vs).
% 5,642,756 inferences, 0.988 CPU in 0.996 seconds (99% CPU, 5710827 Lips)
1 96 15 2 97 14 80 98 13 79
93 29 68 94 30 27 34 31 26 35
16 3 100 17 4 99 12 9 81 45
69 95 92 28 67 32 25 36 33 78
84 18 5 83 19 10 82 46 11 8
91 23 70 63 24 37 66 49 38 44
72 88 20 73 6 47 76 7 41 77
85 62 53 86 61 64 39 58 65 50
90 22 71 89 21 74 42 48 75 43
54 87 60 55 52 59 56 51 40 57
Vs = [4, 5, 21, 22, 8, 3, 29, 26, 6|...]
For utmost performance, I recommend you also try this with other Prolog systems. The efficiency of commercial-grade CLP(FD) systems is often an important reason for buying a Prolog system.
Note also that this is by no means the only promising Prolog or even CLP(FD) formulation of the task, and I leave thinking about other formulations as a challenge.
I'm trying to figure out if I have an infinite loop in my Prolog program, or if I just did a bad job of writing it, so its slow. I'm trying to solve the square sum chains problem from the dailyprogrammer subreddit. Given a number N, find an ordering of the numbers 1-N (inclusive) such that the sum of each pair of adjacent numbers in the ordering is a perfect square. The smallest N that this holds for is 15, with the ordering [8, 1, 15, 10, 6, 3, 13, 12, 4, 5, 11, 14, 2, 7, 9]. This is the code that I'm trying to use to solve the problem:
is_square(Num):- is_square_help(Num, 0).
is_square_help(Num, S):- Num =:= S * S.
is_square_help(Num, S):-
Num > S * S,
T is S+1,
is_square_help(Num, T).
is_square_help(Num, S):- Num < S * S, fail.
contains(_, []):- fail.
contains(Needle, [Needle|_]).
contains(Needle, [_|Tail]):- contains(Needle, Tail).
nums(0, []).
nums(Num, List) :- length(List, Num), nums_help(Num, List).
nums_help(0, _).
nums_help(Num, List) :-
contains(Num, List),
X is Num - 1,
nums_help(X, List).
square_sum(Num, List) :-
nums(Num, List),
square_sum_help(List).
square_sum_help([X, Y|T]) :-
Z is X + Y,
is_square(Z),
square_sum_help(T).
Currently, when I run square_sum(15, List)., the program does not terminate. I've left it alone for about 10 minutes, and it just keeps running. I know that there are problems that take a long time to solve, but others are reportedly generating answers in the order of milliseconds. What am I doing wrong here?
SWI-Prolog allows this compact implementation
square_sum(N,L) :-
numlist(1,N,T),
select(D,T,R),
adj_squares(R,[D],L).
adj_squares([],L,R) :- reverse(L,R).
adj_squares(T,[S|Ss],L) :-
select(D,T,R),
float_fractional_part(sqrt(S+D))=:=0,
adj_squares(R,[D,S|Ss],L).
that completes really fast for N=15
edit as suggested, building the list in order yields better code:
square_sum(N,L) :-
numlist(1,N,T),
select(D,T,R),
adj_squares(R,D,L).
adj_squares([],L,[L]).
adj_squares(T,S,[S|L]) :-
select(D,T,R),
float_fractional_part(sqrt(S+D))=:=0,
adj_squares(R,D,L).
edit
the code above becomes too slow when N grows. I've changed strategy, and attempt now to find an Hamiltonian path into the graph induced by the binary relation. For N=15 it looks like
(here is the code to generate the Graphviz script:
square_pairs(N,I,J) :-
between(1,N,I),
I1 is I+1,
between(I1,N,J),
float_fractional_part(sqrt(I+J))=:=0.
square_pairs_graph(N) :-
format('graph square_pairs_N_~d {~n', [N]),
forall(square_pairs(N,I,J), format(' ~d -- ~d;~n', [I,J])),
writeln('}').
)
and here the code for lookup a path
hamiltonian_path(N,P) :-
square_pairs_struct(N,G),
between(1,N,S),
extend_front(1,N,G,[S],P).
extend_front(N,N,_,P,P) :- !.
extend_front(Len,Tot,G,[Node|Ins],P) :-
arg(Node,G,Arcs),
member(T,Arcs),
\+memberchk(T,Ins),
Len1 is Len+1,
extend_front(Len1,Tot,G,[T,Node|Ins],P).
struct_N_of_E(N,E,S) :-
findall(E,between(1,N,_),As),
S=..[graph|As].
square_pairs_struct(N,G) :-
struct_N_of_E(N,[],G),
forall(square_pairs(N,I,J), (edge(G,I,J),edge(G,J,I))).
edge(G,I,J) :-
arg(I,G,A), B=[J|A], nb_setarg(I,G,B).
Here is a solution using Constraint Logic Programming:
squares_chain(N, Cs) :-
numlist(1, N, Ns),
phrase(nums_partners(Ns, []), NPs),
group_pairs_by_key(NPs, Pairs),
same_length(Ns, Pairs),
pairs_values(Pairs, Partners),
maplist(domain, Is0, Partners),
circuit([D|Is0]),
labeling([ff], Is0),
phrase(chain_(D, [_|Is0]), Cs).
chain_(1, _) --> [].
chain_(Pos0, Ls0) --> [Pos],
{ Pos0 #> 1, Pos #= Pos0 - 1,
element(Pos0, Ls0, E) },
chain_(E, Ls0).
plus_one(A, B) :- B #= A + 1.
domain(V, Ls0) :-
maplist(plus_one, Ls0, Ls),
foldl(union_, Ls, 1, Domain),
V in Domain.
union_(N, Dom0, Dom0\/N).
nums_partners([], _) --> [].
nums_partners([N|Rs], Ls) -->
partners(Ls, N), partners(Rs, N),
nums_partners(Rs, [N|Ls]).
partners([], _) --> [].
partners([L|Ls], N) -->
( { L + N #= _^2 } -> [N-L]
; []
),
partners(Ls, N).
Sample query and answers:
?- squares_chain(15, Cs).
Cs = [9, 7, 2, 14, 11, 5, 4, 12, 13|...] ;
Cs = [8, 1, 15, 10, 6, 3, 13, 12, 4|...] ;
false.
A longer sequence:
?- time(squares_chain(100, Cs)).
15,050,570 inferences, 1.576 CPU in 1.584 seconds (99% CPU, 9549812 Lips)
Cs = [82, 87, 57, 24, 97, 72, 28, 21, 60|...] .
What you are doing wrong is mainly that you generate the whole list before you start testing.
The two clauses that call fail are pointless. Removing them will not change the program. The only reason for doing that is if you do something side-effect-y, like printing output.
Your code for generating the list, and all permutations, seems to work, but it can be done much simpler by using select/3.
You don't seem to have a base case in square_sum_help/1, and you also seem to only check every other pair, which would have lead to problems in some years or whatever when your program had gotten around to checking the correct ordering.
So, by interleaving the generation and testing, like this
square_sum(Num,List) :-
upto(Num,[],List0),
select(X,List0,List1),
square_sum_helper(X,List1,[],List).
square_sum_helper(X1,Rest0,List0,List) :-
select(X2,Rest0,Rest),
Z is X1 + X2,
is_square(Z,0),
square_sum_helper(X2,Rest,[X1|List0],List).
square_sum_helper(_,[],List0,List) :- reverse(List0,List).
is_square(Num,S) :-
Sqr is S * S,
( Num =:= Sqr ->
true
; Num > Sqr,
T is S + 1,
is_square(Num,T) ).
upto(N,List0,List) :-
( N > 0 ->
M is N - 1,
upto(M,[N|List0],List)
; List = List0 ).
the correct result is produced in around 9 msec (SWI Prolog).
?- ( square_sum(15,List), write(List), nl, fail ; true ).
[8,1,15,10,6,3,13,12,4,5,11,14,2,7,9]
[9,7,2,14,11,5,4,12,13,3,6,10,15,1,8]
?- time(square_sum(15,_)).
% 37,449 inferences, 0.009 CPU in 0.009 seconds (100% CPU, 4276412 Lips)
Edit: fixed some typos.
contains/2:
clause contains(_, []):- fail. is buggy and redundant at best.
you should type in the body !, fail.
But it's not needed because that what is unprovable shouldn't be mentioned (closed world assumption).
btw contains/2 is in fact member/2 (built-in)
Suppose we have the following:
edge(a, 1, 10).
edge(b, 2, 20).
edge(c, 3, 30).
edge(d, 4, 40).
I want to extract a matrix representation (M) of these facts, such that
M = [[a,b,c,d],[1,2,3,4],[10,20,30,40]]
Here's a no-brainer solution:
edgeMatrix(M) :-
findall(A, edge(A, _, _), As),
findall(B, edge(_, B, _), Bs),
findall(C, edge(_, _, C), Cs),
M = [As, Bs, Cs].
There are some problems to this approach, however, viz:
we traverse the database n times, where n is the number of arguments; and
this doesn't generalize very well to an arbitrary n.
So the question is: what is the most idiomatic way to achieve this in Prolog?
What about:
edgeMatrix(M) :-
findall([A,B,C],edge(A,B,C),Trans),
transpose(Trans,M).
Now you can simply import the transpose/2 matrix from clpfd module, or implement one yourself like in this answer (yeah I know that's quite lazy, but what is the point of reinventing the wheel?).
If I run this in swipl, I get:
?- edgeMatrix(M).
M = [[a, b, c, d], [1, 2, 3, 4], [10, 20, 30, 40]].
which looks exactly like you want.
You can of course say that there is still some computational overhead to calculate the transpose/2, but the collecting phase is done only once (and if these are not simply facts, but answers from clauses as well) which can be expensive as well, and furthermore I think a module will implement clauses probably very efficiently anyway.
I don't think you'll find a solution that is both completely general and maximally efficient. Here's a simple solution for N = 3:
edges(Edges) :-
Goal = edge(_A, _B, _C),
findall(Goal, Goal, Edges).
edges_abcs_([], [], [], []).
edges_abcs_([edge(A,B,C)|Edges], [A|As], [B|Bs], [C|Cs]) :-
edges_abcs_(Edges, As, Bs, Cs).
edges_abcs([As, Bs, Cs]) :-
edges(Edges),
edges_abcs_(Edges, As, Bs, Cs).
After adding 100,000 additional edge/3 facts, this performs as follows:
?- time(edges_abcs(M)).
% 200,021 inferences, 0.063 CPU in 0.065 seconds (97% CPU, 3176913 Lips)
M = [[a, b, c, d, 1, 2, 3, 4|...], [1, 2, 3, 4, 1, 2, 3|...], [10, 20, 30, 40, 1, 2|...]].
For comparison, here is the measurement for the implementation from the question:
?- time(edgeMatrix_orig(M)).
% 300,043 inferences, 0.061 CPU in 0.061 seconds (100% CPU, 4896149 Lips)
M = [[a, b, c, d, 1, 2, 3, 4|...], [1, 2, 3, 4, 1, 2, 3|...], [10, 20, 30, 40, 1, 2|...]].
And here is the more general solution based on transpose/2 by Willem:
?- time(edgeMatrix_transpose(M)).
% 700,051 inferences, 0.098 CPU in 0.098 seconds (100% CPU, 7142196 Lips)
M = [[a, b, c, d, 1, 2, 3, 4|...], [1, 2, 3, 4, 1, 2, 3|...], [10, 20, 30, 40, 1, 2|...]].
So my solution seems best in terms of number of inferences: 100,000 inferences for the findall/3 and 100,000 inferences for traversing the list. The solution from the question has 100,000 inferences for each findall/3, but nothing more. It is, however, slightly faster because it's more memory efficient: Everything that is allocated ends up in the final solution, whereas my program allocates a list of 100,000 edge/3 terms which must then be garbage collected. (In SWI-Prolog, you can see the garbage collections if you turn on the profiler and/or GC tracing.)
If I really needed this to be as fast as possible and to be generalizable to many different values of N, I'd write a macro that expands to something like the solution in the question.
Edit: If the "idiomatic" requirement is lifted, I would resort to storing the edge database as a list in an SWI-Prolog global variable. In that case, my single-pass implementation would work without the findall/3 overhead and without producing intermediate garbage.
I am doing this problem but I am completely new to Prolog and I have no idea how to do it.
Nine parts of an electronic board have square shape, the same size and each edge of every part is marked with a letter and a plus or minus sign. The parts are to be assembled into a complete board as shown in the figure below such that the common edges have the same letter and opposite signs. Write a planner in Prolog such that the program takes 'assemble' as the query and outputs how to assemble the parts, i.e. determine the locations and positions of the parts w.r.t. the current positions so that they fit together to make the complete board.
I have tried solving it and I have written the following clauses:
complement(a,aNeg).
complement(b,bNeg).
complement(c,cNeg).
complement(d,dNeg).
complement(aNeg,a).
complement(bNeg,b).
complement(cNeg,c).
complement(dNeg,d).
% Configuration of boards, (board,left,top,right,bottom)
conf(b1,aNeg,bNeg,c,d).
conf(b2,bNeg,a,d,cNeg).
conf(b3,dNeg,cNeg,b,d).
conf(b4,b,dNeg,cNeg,d).
conf(b5,d,b,cNeg,aNeg).
conf(b6,b,aNeg,dNeg,c).
conf(b7,aNeg,bNeg,c,b).
conf(b8,b,aNeg,cNeg,a).
conf(b9,cNeg,bNeg,a,d).
position(b1,J,A).
position(b2,K,B).
position(b3,L,C).
position(b4,M,D).
position(b5,N,E).
position(b6,O,F).
position(b7,P,G).
position(b8,Q,H).
position(b9,R,I).
assemble([A,B,C,E,D,F,G,H,I,J,K,L,M,N,O,P,Q,R]) :-
Variables=[(A,J),(B,K),(C,L),(D,M),(E,N),(F,O),(G,P),(H,Q),(I,R)],
all_different(Variables),
A in 1..3, B in 1..3, C in 1..3, D in 1..3, E in 1..3,
F in 1..3, G in 1..3, H in 1..3, I in 1..3, J in 1..3,
K in 1..3, L in 1..3, M in 1..3, N in 1..3, O in 1..3,
P in 1..3, Q in 1..3, R in 1..3,
% this is where I am stuck, what to write next
I don't know even if they are correct and I am not sure how to proceed further to solve this problem.
Trivial with CLP(FD):
:- use_module(library(clpfd)).
board(Board) :-
Board = [[A1,A2,A3],
[B1,B2,B3],
[C1,C2,C3]],
maplist(top_bottom, [A1,A2,A3], [B1,B2,B3]),
maplist(top_bottom, [B1,B2,B3], [C1,C2,C3]),
maplist(left_right, [A1,B1,C1], [A2,B2,C2]),
maplist(left_right, [A2,B2,C2], [A3,B3,C3]),
pieces(Ps),
maplist(board_piece(Board), Ps).
top_bottom([_,_,X,_], [Y,_,_,_]) :- X #= -Y.
left_right([_,X,_,_], [_,_,_,Y]) :- X #= -Y.
pieces(Ps) :-
Ps = [[-2,3,4,-1], [1,4,-3,-4], [-3,2,4,-4],
[-4,-3,4,2], [2,-3,-1,4], [-1,-4,3,2],
[-2,3,2,-1], [-1,-3,1,2], [-2,1,4,-3]].
board_piece(Board, Piece) :-
member(Row, Board),
member(Piece0, Row),
rotation(Piece0, Piece).
rotation([A,B,C,D], [A,B,C,D]).
rotation([A,B,C,D], [B,C,D,A]).
rotation([A,B,C,D], [C,D,A,B]).
rotation([A,B,C,D], [D,A,B,C]).
Example query and its result:
?- time(board(Bs)), maplist(writeln, Bs).
11,728,757 inferences, 0.817 CPU in 0.817 seconds
[[-3, -4, 1, 4], [-1, -2, 3, 4], [4, -4, -3, 2]]
[[-1, 4, 2, -3], [-3, 4, 2, -4], [3, 2, -1, -4]]
[[-2, 1, 4, -3], [-2, 3, 2, -1], [1, 2, -1, -3]]
This representation uses 1,2,3,4 to denote positive a,b,c,d, and -1,-2,-3,-4 for the negative ones.
This is only a tiny improvement to #mat's beautiful solution. The idea is to reconsider the labeling process. That is maplist(board_piece,Board,Ps) which reads (semi-procedurally):
For all elements in Ps, thus for all pieces in that order: Take one piece and place it anywhere on the board rotated or not.
This means that each placement can be done in full liberty. To show you a weak order, one might take: A1,A3,C1,C3,B2 and then the rest. In this manner, the actual constraints are not much exploited.
However, there seems to be no good reason that the second tile is not placed in direct proximity to the first. Here is such an improved order:
...,
pieces(Ps),
TilesOrdered = [B2,A2,A3,B3,C3,C2,C1,B1,A1],
tiles_withpieces(TilesOrdered, Ps).
tiles_withpieces([], []).
tiles_withpieces([T|Ts], Ps0) :-
select(P,Ps0,Ps1),
rotation(P, T),
tiles_withpieces(Ts, Ps1).
Now, I get
?- time(board(Bs)), maplist(writeln, Bs).
% 17,179 inferences, 0.005 CPU in 0.005 seconds (99% CPU, 3363895 Lips)
[[-3,1,2,-1],[-2,3,2,-1],[2,4,-4,-3]]
[[-2,1,4,-3],[-2,3,4,-1],[4,2,-4,-3]]
[[-4,3,2,-1],[-4,1,4,-3],[4,2,-3,-1]]
and without the goal maplist(maplist(tile), Board),
% 11,010 inferences, 0.003 CPU in 0.003 seconds (100% CPU, 3225961 Lips)
and to enumerate all solutions
?- time((setof(Bs,board(Bs),BBs),length(BBs,N))).
% 236,573 inferences, 0.076 CPU in 0.154 seconds (49% CPU, 3110022 Lips)
BBs = [...]
N = 8.
previously (#mat's original version) the first solution took:
% 28,874,632 inferences, 8.208 CPU in 8.217 seconds (100% CPU, 3518020 Lips)
and all solutions:
% 91,664,740 inferences, 25.808 CPU in 37.860 seconds (68% CPU, 3551809 Lips)
In terms of performance, the following is no contender to #false's very fast solution.
However, I would like to show you a different way to formulate this, so that you can use the constraint solver to approximate the faster allocation strategy that #false found manually:
:- use_module(library(clpfd)).
board(Board) :-
Board = [[A1,A2,A3],
[B1,B2,B3],
[C1,C2,C3]],
maplist(top_bottom, [A1,A2,A3], [B1,B2,B3]),
maplist(top_bottom, [B1,B2,B3], [C1,C2,C3]),
maplist(left_right, [A1,B1,C1], [A2,B2,C2]),
maplist(left_right, [A2,B2,C2], [A3,B3,C3]),
pieces(Ps0),
foldl(piece_with_id, Ps0, Pss, 0, _),
append(Pss, Ps),
append(Board, Bs0),
maplist(tile_with_var, Bs0, Bs, Vs),
all_distinct(Vs),
tuples_in(Bs, Ps).
tile_with_var(Tile, [V|Tile], V).
top_bottom([_,_,X,_], [Y,_,_,_]) :- X #= -Y.
left_right([_,X,_,_], [_,_,_,Y]) :- X #= -Y.
pieces(Ps) :-
Ps = [[-2,3,4,-1], [1,4,-3,-4], [-3,2,4,-4],
[-4,-3,4,2], [2,-3,-1,4], [-1,-4,3,2],
[-2,3,2,-1], [-1,-3,1,2], [-2,1,4,-3]].
piece_with_id(P0, Ps, N0, N) :-
findall(P, (rotation(P0,P1),P=[N0|P1]), Ps),
N #= N0 + 1.
rotation([A,B,C,D], [A,B,C,D]).
rotation([A,B,C,D], [B,C,D,A]).
rotation([A,B,C,D], [C,D,A,B]).
rotation([A,B,C,D], [D,A,B,C]).
You can now use the "first fail" strategy of CLP(FD) and try the most constrained elements first. With this formulation, the time needed to find all 8 solutions is:
?- time(findall(t, (board(B), term_variables(B, Vs), labeling([ff],Vs)), Ts)).
2,613,325 inferences, 0.208 CPU in 0.208 seconds
Ts = [t, t, t, t, t, t, t, t].
In addition, I would like to offer the following contender for the speed contest, which I obtained with an extensive partial evaluation of the original program:
solution([[[-4,-3,2,4],[2,-1,-4,3],[2,-1,-3,1]],[[-2,3,4,-1],[4,2,-4,-3],[3,2,-1,-2]],[[-4,1,4,-3],[4,2,-3,-1],[1,4,-3,-2]]]).
solution([[[-3,-4,1,4],[-1,-2,3,4],[4,-4,-3,2]],[[-1,4,2,-3],[-3,4,2,-4],[3,2,-1,-4]],[[-2,1,4,-3],[-2,3,2,-1],[1,2,-1,-3]]]).
solution([[[-3,-2,1,4],[-3,-1,4,2],[4,-3,-4,1]],[[-1,-2,3,2],[-4,-3,4,2],[4,-1,-2,3]],[[-3,1,2,-1],[-4,3,2,-1],[2,4,-4,-3]]]).
solution([[[-3,1,2,-1],[-2,3,2,-1],[2,4,-4,-3]],[[-2,1,4,-3],[-2,3,4,-1],[4,2,-4,-3]],[[-4,3,2,-1],[-4,1,4,-3],[4,2,-3,-1]]]).
solution([[[-3,-1,4,2],[4,-3,-4,1],[2,-1,-4,3]],[[-4,-3,4,2],[4,-1,-2,3],[4,-3,-2,1]],[[-4,-3,2,4],[2,-1,-2,3],[2,-1,-3,1]]]).
solution([[[-1,-3,1,2],[2,-1,-2,3],[4,-3,-2,1]],[[-1,-4,3,2],[2,-4,-3,4],[2,-3,-1,4]],[[-3,2,4,-4],[3,4,-1,-2],[1,4,-3,-4]]]).
solution([[[-1,-4,3,2],[-3,-2,1,4],[-1,-3,1,2]],[[-3,-4,1,4],[-1,-2,3,4],[-1,-2,3,2]],[[-1,4,2,-3],[-3,4,2,-4],[-3,2,4,-4]]]).
solution([[[4,-4,-3,2],[2,-4,-3,4],[2,-3,-1,4]],[[3,2,-1,-2],[3,4,-1,-2],[1,4,-3,-4]],[[1,2,-1,-3],[1,4,-3,-2],[3,2,-1,-4]]]).
The 8 solutions are found very rapidly with this formulation:
?- time(findall(t, solution(B), Ts)).
19 inferences, 0.000 CPU in 0.000 seconds
Ts = [t, t, t, t, t, t, t, t].