user27815
user27815

Reputation: 4797

Bridge crossing puzzle with clpfd

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.

Upvotes: 3

Views: 1522

Answers (4)

CapelliC
CapelliC

Reputation: 60034

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)

Upvotes: 3

mat
mat

Reputation: 40768

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!

Upvotes: 5

user27815
user27815

Reputation: 4797

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).

Upvotes: 1

Paulo Moura
Paulo Moura

Reputation: 18663

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.

Upvotes: 0

Related Questions