2/**********************************************************************
    3 *
    4 * @(#) testMotel.pl 1.4@(#)
    5 *
    6 */
    7
    8testMotel0 :-
    9	testAllMotelExamples(1),
   10	!.
   11
   12testMotel(N) :-
   13	testAllMotelExamples(N),
   14	!.
   15
   16testAllMotelExamples(61) :-
   17	print('Test complete'), nl, nl,
   18	!.
   19testAllMotelExamples(N) :-
   20	initializeMotel,
   21	print('Example '), print(N), nl, example(N),
   22	once(testMotelExample(N)),
   23	M is N + 1,
   24	testAllMotelExamples(M).
   25
   26testMotelExample(1) :-	
   27	no_goal.
   28testMotelExample(2) :-
   29	printTime(setof(C,E^deduce(ex2,[],elementOf(mary,C),E),L1)), print(L1), nl,
   30	printTime(setof(D,F^deduce(ex2,[],elementOf(tom,D),F),L2)), print(L2), nl.
   31testMotelExample(3) :-
   32	tryGoal(inconsistent(ex3)).
   33testMotelExample(4) :-
   34	no_goal.
   35testMotelExample(5) :-
   36	tryGoal(not(subsumes([],c1,c2))),
   37	tryGoal(subsumes([],c2,c1)).
   38testMotelExample(6) :-
   39	tryGoal(not(subsumes([],c1,c2))),
   40	tryGoal(subsumes([],c2,c1)).
   41testMotelExample(7) :-
   42	no_goal.
   43testMotelExample(8) :-
   44	tryGoal(deduce(elementOf(tom,heterosexual))).
   45testMotelExample(9) :-
   46	tryGoal(deduce(elementOf(chris,male))).
   47testMotelExample(10) :-
   48	tryGoal(deduce(elementOf(tom,c2))).
   49testMotelExample(11) :-
   50	tryGoal(inconsistent(ex11)).
   51testMotelExample(12) :-
   52	tryGoal(subsumes([],c1,c2)),
   53	tryGoal(not(subsumes([],c2,c1))).
   54testMotelExample(13) :-
   55	tryGoal(subsumes([],c1,c2)).
   56testMotelExample(14) :-
   57%	initializeMotel, print('Example 14'), nl, example(14),
   58%	tryGoal(subsumes([],c2,c1)),
   59	!.
   60testMotelExample(15) :-
   61	tryGoal(subsumes([],c2,c1)).
   62testMotelExample(16) :-
   63	tryGoal(subsumes([],c2,c1)).
   64testMotelExample(17) :-
   65	tryGoal(subsumes([],c2,c1)).
   66testMotelExample(18) :-
   67	tryGoal(deduce(elementOf(mary,c4))).
   68testMotelExample(19) :-
   69	tryGoal(deduce(elementOf(amy,female))).
   70testMotelExample(20) :-
   71	tryGoal(inconsistent(ex20)).
   72testMotelExample(21) :-
   73	no_goal,
   74% 	deduce(elementOf(betty,female)),
   75	!.
   76testMotelExample(22) :-
   77% 	deduce(elementOf(amy,female)),
   78	no_goal.
   79testMotelExample(23) :-
   80% 	deduce(elementOf(amy,female))
   81	no_goal.
   82testMotelExample(24) :-
   83	tryGoal(deduce(elementOf(audi,c3))).
   84testMotelExample(25) :-
   85	tryGoal(not(deduce(elementOf(audi,c3)))).
   86testMotelExample(26) :-
   87	tryGoal(not(subsumes([],c1,c2))),
   88	tryGoal(subsumes([],c2,c1)).
   89testMotelExample(27) :-
   90	tryGoal(not(subsumes([],c1,c2))),
   91	tryGoal(subsumes([],c2,c1)).
   92testMotelExample(28) :-
   93	tryGoal(deduce(ex29,[b(believe,john)],elementOf(audi,auto),_P)).
   94testMotelExample(29) :-
   95	no_goal.
   96testMotelExample(30) :-
   97	no_goal.
   98testMotelExample(31) :-
   99	tryGoal(deduce(elementOf(tom,onlyMaleChildren))).
  100testMotelExample(32) :-
  101	tryGoal(abduce(_H1,elementOf(robin,male),_E1)),
  102	tryGoal(abduce(_H2,elementOf(robin,female),_E2)).
  103testMotelExample(33) :-
  104	tryGoal(abduce(_H3,elementOf(nixon,dove),_E3)),
  105	tryGoal(abduce(_H4,elementOf(nixon,hawk),_E4)).
  106testMotelExample(34) :-
  107	tryGoal(inconsistent(ex34)).
  108testMotelExample(35) :-
  109	tryGoal(abduce(ex35,[],_H5,elementOf(john,fly),_E5)),
  110	tryGoal(not(abduce(ex35,[],_H8,elementOf(tweety,fly),_E8))).
  111testMotelExample(36) :-
  112	tryGoal(abduce(ex36,[],_H6,elementOf(nixon,dove),_E6)),
  113	tryGoal(abduce(ex36,[],_H7,elementOf(nixon,hawk),_E7)).
  114testMotelExample(37) :-
  115	no_goal.
  116testMotelExample(38) :-
  117	tryGoal(deduce(elementOf(ideaste,c2))).
  118testMotelExample(39) :-
  119	tryGoal(deduce(elementOf(lucky,female))),
  120	tryGoal(assert_ind(lucky,male)),
  121	tryGoal(not(deduce(elementOf(lucky,female)))),
  122	tryGoal(consistent([])).
  123testMotelExample(40) :-
  124	tryGoal(deduce(elementOf(peter,richPerson))),
  125	tryGoal(assert_ind(peter,poorPerson)),
  126	tryGoal(not(deduce(elementOf(peter,richPerson)))),
  127	tryGoal(consistent([])),
  128	tryGoal(not(subsumes(richPerson,doctor))).
  129testMotelExample(41) :-
  130	tryGoal(deduce(elementOf(tom,richPerson))),
  131	tryGoal(assert_ind(tom,poorPerson)),
  132	tryGoal(not(deduce(elementOf(tom,richPerson)))),
  133	tryGoal(consistent([])).
  134testMotelExample(42) :-
  135	tryGoal(deduce(elementOf(audi,fourWheels))),
  136	tryGoal(assert_ind(audi,fiveWheels)),
  137	tryGoal(not(deduce(elementOf(audi,fourWheels)))),
  138	tryGoal(consistent([])).
  139testMotelExample(43) :-
  140	tryGoal(deduce(elementOf(r,red))),
  141	tryGoal(deduce(elementOf(r,redOrYellow))),
  142	tryGoal(deduce(elementOf(r,colors))).
  143testMotelExample(44) :-
  144	tryGoal(subsumes(c2,c12)).
  145testMotelExample(45) :-
  146	no_goal.
  147testMotelExample(46) :-
  148	no_goal.
  149testMotelExample(47) :-
  150	tryGoal(deduce(elementOf(bmw,c3))).
  151testMotelExample(48) :-
  152	no_goal.
  153testMotelExample(49) :-
  154	tryGoal(not(deduce(elementOf(p,c4)))).
  155testMotelExample(50) :-
  156	tryGoal(deduce(elementOf(peter,c0))).
  157
  158testMotelExample(51) :-
  159	tryGoal(deduce(posInfl(a,d))),
  160	tryGoal(deduce(posInfl(b,d))),
  161	tryGoal(bagof(Y1,deduce(posInfl(a,Y1)),Y1s)),
  162	verifySolution(Y1s,[b,c,d,g]),
  163	tryGoal(deduce(infl(a,d,1.0))),
  164	tryGoal(bagof((X1,W1),deduce(infl(X1,e,W1)),X1W1Pairs)),
  165	verifySolution(X1W1Pairs,[(a,0.0),(b,-1.0),(g,1.0)]),
  166	tryGoal(deduce(simultInfl([a,h],d,2.0))),
  167	tryGoal(deduce(change(d,1.0))),
  168	tryGoal(bagof(X2,deduce(increase(X2)),X2s)),
  169	verifySolution(X2s,[b,c,d,g,a]).
  170
  171testMotelExample(52) :-
  172	tryGoal(deduce(negInfl(withRebate,hasOverallCost))),
  173	tryGoal(deduce(posInfl(hasListPrice,hasOverallCost))),
  174	tryGoal(deduce(posInfl(hasCubicCapacity,hasPrice))),
  175	tryGoal(deduce(posInfl(hasCubicCapacity,hasOverallCost))),
  176	tryGoal(deduce(posInfl(hasCatConverter,hasOverallCost))),
  177	tryGoal(deduce(simultInfl([hasCubicCapacity,hasCatConverter],hasOverallCost,3.0))),
  178	tryGoal(deduce(simultInfl([hasCubicCapacity,hasCatConverter],hasMaxSpeed,-1.0))),
  179	tryGoal(deduce(leastInfl(hasCubicCapacity,hasMaxSpeed))),
  180	tryGoal(deduce(leastInfls([hasCatConverter,hasCubicCapacity],hasMaxSpeed))),
  181	tryGoal(deduce(maxPosInfl(hasCubicCapacity,hasOverallCost,2.0))),
  182	tryGoal(bagof((X1,W1),deduce(maxNegInfl(X1,hasMaxSpeed,W1)),X1W1Pairs)),
  183	verifySolution(X1W1Pairs,[(hasCatConverter,-1.0),(hasWeight,-1.0)]),
  184	tryGoal(bagof(X2,deduce(increase(X2)),X2s)),
  185	verifySolution(X2s,[hasFuelConsumption,hasListPrice,hasOverallCost,hasPrice,hasWeight,hasCubicCapacity]),
  186	tryGoal(bagof((X3,W3),(deduce(leastInfl(X3,hasMaxSpeed)),abduce(change(X3,W3),change(hasMaxSpeed,1.0))),X3W3s)),
  187	verifySolution(X3W3s,[(hasCatConverter,-1.0)]).
  188testMotelExample(53) :-
  189	no_goal.
  190testMotelExample(54) :-
  191	no_goal.
  192testMotelExample(55) :-
  193	no_goal.
  194testMotelExample(56) :-
  195	no_goal.
  196testMotelExample(57) :-
  197	no_goal.
  198testMotelExample(58) :-
  199	no_goal.
  200testMotelExample(59) :-
  201	tryGoal(sb_ask(isa(harry,parent))),
  202	tryGoal(sb_ask(isa(harry,person))),
  203	printTime(setof((X,Y),sb_ask(role(child,X,Y)),L1)), print(L1), nl,
  204	printTime(setof(X,sb_ask(roleDef(child,X)),L2)), print(L2), nl,
  205	printTime(setof((X,Y),sb_ask(roleNr('marys-child',X,Y)),L3)), print(L3), nl,
  206	printTime(setof(X,sb_ask(roleDefNr('marys-child',X)),L4)), print(L4), nl.
  207testMotelExample(60) :-
  208	tryGoal(deduce(ex60,[b(believe,peter)],elementOf(tom,richPerson),E)),
  209	tryGoal(assert_ind([b(believe,peter)],tom,not(richPerson))),
  210	tryGoal(inconsistent([b(believe,peter)])).
  211
  212
  213tryGoal(G) :-
  214	call(G),
  215	!,
  216	print('Goal '), print(G), print(' succeeded'), nl.
  217tryGoal(G) :-
  218	print('Goal '), print(G), print(' failed'), nl.
  219
  220/***********************************************************************
  221 *
  222 * verifySolution(+TestSol,+ExpectedSol)
  223 *
  224 *	prints an error message if TestSol and ExpectedSol do not
  225 *	match.
  226 */
  227
  228verifySolution(TestSol,ExpectedSol) :-
  229	nonvar(ExpectedSol),
  230	nonvar(TestSol),
  231	!,
  232	TestSol = ExpectedSol.
  233verifySolution(TestSol,ExpectedSol) :-
  234	print('Solutions differ: test solution is '),
  235	print(TestSol),
  236	print(', while expected solution is '),
  237	print(ExpectedSol)