2

I am trying to solve this puzzle in prolog

Five people were eating apples, A finished before B, but behind C. D finished before E, but behind B. What was the finishing order?

My current solution has singleton variable, I am not sure how to fix this.

finishbefore(A, B, Ls) :- append(_, [A,B|_], Ls).

order(Al):-
   length(Al,5),
   finishbefore(A,B,Al),
   finishbefore(C,A,Al),
   finishbefore(D,E,Al),
   finishbefore(B,D,Al).
%%query
%%?- order(Al).
false
  • 10,264
  • 13
  • 101
  • 209
Boxiang
  • 23
  • 2

2 Answers2

2

Here is a pure version using constraints of library(clpz) or library(clpfd). The idea is to ask for a slightly different problem.

How can an endpoint in time be associated to each person respecting the constraints given?

Since we have five persons, five different points in time are sufficient but not strictly necessary, like 1..5.

:- use_module(library(clpz)).  % or clpfd
:- set_prolog_flag(double_quotes, chars).  % for "abcde" below.

appleeating_(Ends, Zs) :-
    Ends = [A,B,C,D,E],
    Zs = Ends,
    Ends ins 1..5,
    % alldifferent(Ends),
    A #< B,
    C #< A,
    D #< E,
    B #< D.

?- appleeating_(Ends, Zs).
   Ends = [2, 3, 1, 4, 5], Zs = [2, 3, 1, 4, 5].

There is exactly one solution! Note that alldifferent/1 is not directly needed since nowhere is it stated that two persons are not allowed to end at precisely the same time. In fact, above proves that there is no shorter solution. @CapelliC's solution imposes an order, even if two persons finish ex aequo. But for the sake of compatibility, lets now map the solution back to your representation.

list_nth1(Es, N, E) :-
    nth1(N, Es, E).

appleeatingorder(OrderedPeople) :-
    appleeating_(Ends, Zs),
    same_length(OrderedPeople, Ends),
    labeling([], Zs), % not strictly needed
    maplist(list_nth1(OrderedPeople), Ends,"abcde").  % effectively enforces alldifferent/1

?- appleeatingorder(OrderedPeople).
   OrderedPeople = [c,a,b,d,e].
?- appleeatingorder(OrderedPeople).
   OrderedPeople = "cabde".

The last solution using double quotes produces Scryer directly. In SWI use library(double_quotes).

(The extra argument Zs of appleeating_/2 is not strictly needed in this case, but it is a very useful convention for CLP predicates in general. It separates the modelling part (appleeating_/2) from the search part (labeling([], Zs)) such that you can easily try various versions for search/labeling at the same time. In order to become actually solved, all variables in Zs have to have an actual value.)

false
  • 10,264
  • 13
  • 101
  • 209
0

Let's correct finishbefore/3:

finishbefore(X, Y, L) :-
  append(_, [X|R], L),
  memberchk(Y, R).

then let's encode the known constraints:

check_finish_time(Order) :-
  forall(
    member(X<Y, [a<b,c<a, d<e,d<b]),
    finishbefore(X,Y,Order)).

and now let's test all possible orderings

?- permutation([a,b,c,d,e],P),check_finish_time(P).

I get 9 solutions, backtracking with ;... maybe there are implicit constraints that should be encoded.

edit

Sorry for the noise, have found the bug. Swap the last constraint order, that is b<d instead of d<b, and now only 1 solution is allowed...

CapelliC
  • 59,646
  • 5
  • 47
  • 90