failure slice - Prolog: Trying to solve a puzzle! returned false -


the code @ end on post supposed answer following puzzle:

brown, clark, jones , smith 4 substantial citizens serve community achitect, banker, doctor , lawyer, though not respectively. brown, more conservative jones more liberal smith, better golfer men younger , has larger income men older clark. banker, earns more architect, neither youngest nor oldest.

the doctor, poorer golfer lawyer, less conservative architect. might expected, oldest man conservative , has largest income, , youngest man best golfer. each man's profession?

code:

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % % represent each "person" six-tuple of form % % [ name , profession , age , income , politics , golf ranking ] % % name either brown, clark, jones, or smith %       profession either banker, lawyer, doctor, or architect %       age range 1 .. 4, 1 being youngest , 4 oldest %       income range 1 .. 4, 1 being least , 4 %       politics range 1 .. 4, 1 being conservative, 4 liberal %       golf ranking range 1 .. 4, 1 best rank, 4 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, more conservateive jones % more liberal smith, better golfer % men younger , has larger % income men older 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) ).  % men younger brown better golfer ===> % not case there exists man younger brown % such brown not better golfer him. % "is not case" 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)).  % men older clark, brown makes more money ===> % not case there exists man older clark such % brown not make more money him. % "is not case" 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 % banker, earns more archiect, % neither youngest nor 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 % doctor, pooer golfer lawyer, % less conservative 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 % might expected, oldest man % conservative , has largest income, ,  % youngest man 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 run it, returns false!

?- solutions(l). false. 

could me please?

i won't solve whole issue you, explain general approach lets narrow down such issues.

to recap, have 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 most general query, arguments fresh variables:

 ?- solutions(l). false. 

why fail? in gupu, use , using following definition generalize away goals:

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

if include in program, can use (*)/1 in front of goals "strike them out". can make resulting program @ more general.

for example, let generalize away all goals (i using strikeout text indicate goal no longer constrains solution because 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 query succeeds:

 ?- solutions(l). true. 

however, program too general now. point: can selectively re-introduce goals (= constraints) locate mistakes cause unintended failure of program.

for example, pick first goal, , clue2/1 goal, , remove (*)/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 have:

 ?- solutions(l). false. 

from this, know clue2/1 must contain mistake. because further goals can make predicate @ still more specific, , cannot remove failure of goal.

let reconsider 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 in using non-monotonic predicate not/1, incorrectly removes solutions in case. check out, general query, no answers predicate:

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

what do? answer:

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

constraints true relations , can used in directions, if or of arguments free variables!

in case, use either dif/2 or, better in case, clp(fd) constraint (#\=)/2 express 2 integers different:

 clue2(l) :-         member(p1,l), member(p2,l),         p1 = [_, banker, a1, i1, _, _],         p2 = [_, architect, _, i2, _, _],         richer(p1,p2),         a1 #\= 1,         a1 #\= 4. 

with simple change, predicate yields answers, , narrowed down program succeeds general query.

by systematically applying declarative debugging technique, can correct remaining mistakes in other predicates. leave exercise.


Comments

Popular posts from this blog

asynchronous - C# WinSCP .NET assembly: How to upload multiple files asynchronously -

aws api gateway - SerializationException in posting new Records via Dynamodb Proxy Service in API -

asp.net - Problems sending emails from forum -