Search code examples
prologfailure-slicezebra-puzzle

Prolog: Trying to solve a puzzle! returned false


The code at the end on my post is supposed to answer the following puzzle:

Brown, Clark, Jones and Smith are 4 substantial citizens who serve their community as achitect, banker, doctor and lawyer, though not necessarily respectively. Brown, who is more conservative than Jones but more liberal than Smith, is a better golfer than the men who are YOUNGER than he is and has a larger income than the men who are OLDER than Clark. The banker, who earns more than the architect, is neither the youngest nor the oldest.

The doctor, who is a poorer golfer than the lawyer, is less conservative than the architect. As might be expected, the oldest man is the most conservative and has the largest income, and the youngest man is the best golfer. What is each man's profession?

code:

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% We represent each "person" with a six-tuple of the form
%
% [ name , profession , age , income , politics , golf ranking ]
%
% where name is either brown, clark, jones, or smith
%       profession is either banker, lawyer, doctor, or architect
%       age is a range 1 .. 4, with 1 being the youngest and 4 the oldest
%       income is a range 1 .. 4, with 1 being the least and 4 the most
%       politics is a range 1 .. 4, with 1 being conservative, 4 liberal
%       golf ranking is a range 1 .. 4, 1 for the best rank, 4 for the worst
%
:- use_module(library(clpfd)).
solutions(L) :- L = [ [brown, _, _, _, _, _], [clark, _, _, _, _, _],
                      [jones, _, _, _, _, _], [smith, _, _, _, _, _] ],
                clue1(L),
                clue2(L),
                clue3(L),
                clue4(L),
                constrained_profession(L),
                constrained_age(L),
                constrained_income(L),
                constrained_politics(L),
                constrained_golf_rank(L).

%
% clue #1
% brown, who is more conservateive than jones but
% more liberal than smith, is a better golfer than
% the men who are younger than he is and has a larger
% income than the men who are older than clark
%

clue1(L) :- member(P1,L), member(P2,L), member(P3,L),
            P1 = [brown, _, A1, _, L1, G1],
            P2 = [jones, _, _, _, L2, _],
            P3 = [smith, _, _, _, L3, _],
            liberaler( P2, P1 ),
            liberaler( P1, P3 ),
            not( clue1_helper_a(L) ),
            not( clue1_helper_b(L) ).

% for all men younger than brown he is a better golfer ===>
% it is not the case that there exists a man younger than brown
% such that brown is not a better golfer than him.
% The "is not the case" is taken care of in clue1.

clue1_helper_a(L) :- member(P1,L), P1 = [brown, _, A1, _, L1, G1],
                     member(PU,L), PU = [_, _, AU, _, _, GU],
                     younger(PU,P1),
                     not(golfier(P1, PU)).

% for all men older than clark, brown makes more money than they do ===>
% it is not the case that there exists a man older than clark such that
% brown does not make more money than him.
% The "is not the case" is taken care of in clue1.

clue1_helper_b(L) :- member(P1,L), P1 = [brown, _, _, _, _, _],
                     member(P2,L), P2 = [clark, _, _, _, _, _],
                     member(PU,L), PU = [_, _, _, _, _, _],
                     younger(P2,PU),
                     not(richer(P1, PU)).

%
% clue #2
% the banker, who earns more than the archiect, is
% neither the youngest nor the oldest
%

clue2(L) :- member(P1,L), member(P2,L),
            P1 = [_, banker, A1, I1, _, _],
            P2 = [_, architect, _, I2, _, _],
            richer(P1,P2),
            not( A1 = 1 ),
            not( A1 = 4 ).

%
% clue #3
% the doctor, who is a pooer golfer than the lawyer, is
% less conservative than the architect. 
%

clue3(L) :- member(P1, L), member(P2, L), member(P3,L),
            P1 = [_,doctor, _, _, L1, G1],
            P2 = [_,lawyer, _, _, _, G2],
            P3 = [_,architect, _, _, L3, _],
            golfier(P2,P1),
            liberaler(P1,P3).

%
% clue #4
% as might be expected, the oldest man is the most
% conservative and has the largest income, and the 
% youngest man is the best golfer.

clue4(L) :- member(P1,L), member(P2,L),
            P1 = [_, _, 4, 4, 1, _],
            P2 = [_, _, 1, _, _, 1].

%
% relations
%

younger(X,Y) :- X = [_, _, AX, _, _, _], Y = [_, _, AY, _, _, _], AX #< AY.

liberaler(X,Y) :- X = [_, _, _, _, LX, _], Y = [_, _, _, _, LY, _], LX #> LY.

golfier(X,Y) :- X = [_, _, _, _, _, GX], Y = [_, _, _, _, _, GY], GX #< GY.

richer(X,Y) :- X = [_, _, _, IX, _, _], Y = [_, _, _, IY, _, _], IX #> IY.

%
% constraints
%

constrained_profession(L) :-
    member(P1,L), member(P2,L), member(P3,L), member(P4,L),
    P1 = [_, banker, _, _, _, _],
    P2 = [_, lawyer, _, _, _, _],
    P3 = [_, doctor, _, _, _, _],
    P4 = [_, architect, _, _, _, _].

constrained_age(L) :-
    member(P1,L), member(P2,L), member(P3,L), member(P4,L),
    P1 = [_, _, 1, _, _, _],
    P2 = [_, _, 2, _, _, _],
    P3 = [_, _, 3, _, _, _],
    P4 = [_, _, 4, _, _, _].

constrained_income(L) :-
    member(P1,L), member(P2,L), member(P3,L), member(P4,L),
    P1 = [_, _, _, 1, _, _],
    P2 = [_, _, _, 2, _, _],
    P3 = [_, _, _, 3, _, _],
    P4 = [_, _, _, 4, _, _].

constrained_politics(L) :-
    member(P1,L), member(P2,L), member(P3,L), member(P4,L),
    P1 = [_, _, _, _, 1, _],
    P2 = [_, _, _, _, 2, _],
    P3 = [_, _, _, _, 3, _],
    P4 = [_, _, _, _, 4, _].

constrained_golf_rank(L) :-
    member(P1,L), member(P2,L), member(P3,L), member(P4,L),
    P1 = [_, _, _, _, _, 1],
    P2 = [_, _, _, _, _, 2],
    P3 = [_, _, _, _, _, 3],
    P4 = [_, _, _, _, _, 4].

% end


%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

However, when I run it, it returns false!

?- solutions(L).
false.

Could anyone help me please?


Solution

  • I won't solve the whole issue for you, but I would like to explain a general approach that lets you quickly narrow down such issues.

    To recap, we have the following main predicate:

    solutions(L) :-
            L = [ [brown, _, _, _, _, _], [clark, _, _, _, _, _],
                  [jones, _, _, _, _, _], [smith, _, _, _, _, _] ],
            clue1(L),
            clue2(L),
            clue3(L),
            clue4(L),
            constrained_profession(L),
            constrained_age(L),
            constrained_income(L),
            constrained_politics(L),
            constrained_golf_rank(L).
    

    It fails unexpectedly even for the most general query, where all arguments are fresh variables:

    ?- solutions(L).
    false.
    

    Why does it fail? As in GUPU, I will use , by using the following definition to generalize away goals:

    :- op(950, fy, *).
    *_.
    

    If you include this in your program, you can use (*)/1 in front of goals to "strike them out". This can make the resulting program at most more general.

    For example, let us generalize away all goals now (I am using strikeout text to indicate that a goal no longer constrains the solution because it is generalized away):

    solutions(L) :-
            * L = [ [brown, _, _, _, _, _], [clark, _, _, _, _, _],    [jones, _, _, _, _, _], [smith, _, _, _, _, _] ],
            * clue1(L),
            * clue2(L),
            * clue3(L),
            * clue4(L),
            * constrained_profession(L),
            * constrained_age(L),
            * constrained_income(L),
            * constrained_politics(L),
            * constrained_golf_rank(L).
    

    Now the query succeeds:

    ?- solutions(L).
    true.
    

    However, the program is clearly too general now. Now the point: We can selectively re-introduce goals (= constraints) to locate mistakes that cause unintended failure of the program.

    For example, I pick the first goal, and the clue2/1 goal, and remove the (*)/1 in front of them:

    solutions(L) :-
            L = [ [brown, _, _, _, _, _], [clark, _, _, _, _, _],
                  [jones, _, _, _, _, _], [smith, _, _, _, _, _] ],
            * clue1(L),
            clue2(L),
            * clue3(L),
            * clue4(L),
            * constrained_profession(L),
            * constrained_age(L),
            * constrained_income(L),
            * constrained_politics(L),
            * constrained_golf_rank(L).
    

    Now, again we have:

    ?- solutions(L).
    false.
    

    From this, you know that clue2/1 must contain a mistake. This is because any further goals can make the predicate at most still more specific, and they cannot remove the failure of this goal.

    Let us reconsider the definition of clue2/1:

    
    clue2(L) :- member(P1,L), member(P2,L),
                P1 = [_, banker, A1, I1, _, _],
                P2 = [_, architect, _, I2, _, _],
                richer(P1,P2),
                not( A1 = 1 ),
                not( A1 = 4 ).
    

    The mistake here is in using the non-monotonic predicate not/1, which incorrectly removes solutions in this case. Check it out, even for a very general query, we get no answers from this predicate:

    ?- length(Ls, 4), clue2(Ls).
    false.
    

    What to do? Answer:

    Instead of not/1 or (\+)/1, use constraints to express disequalities.

    Constraints are true relations and can be used in all directions, even if some or all of its arguments are free variables!

    In your case, use either dif/2 or, better in this case, the CLP(FD) constraint (#\=)/2 to express that two integers are different:

    clue2(L) :-
            member(P1,L), member(P2,L),
            P1 = [_, banker, A1, I1, _, _],
            P2 = [_, architect, _, I2, _, _],
            richer(P1,P2),
            A1 #\= 1,
            A1 #\= 4.
    

    With this simple change, the predicate now yields answers, and the narrowed down program succeeds for the most general query.

    By systematically applying this declarative debugging technique, you can correct the remaining mistakes in the other predicates. I leave this as an exercise.