home *** CD-ROM | disk | FTP | other *** search
/ Power-Programmierung / CD1.mdf / prolog / pdprolog / journey.pro < prev    next >
Text File  |  1986-05-05  |  2KB  |  67 lines

  1. /*  
  2. For a similar program, see Clocksin & Mellish page 165.
  3.  
  4. Plan a trip from place to place.
  5.  
  6. An appropriate question would be:
  7.  
  8. ?-go( darlington, workington, X ).
  9. */
  10.  
  11.   append( [], L, L ).
  12.   append( [Z|L1], L2, [Z|L3] ) :- append( L1, L2, L3 ).
  13.   printstring( [] ).
  14.   printstring( [H|T] ) :- put( H ), printstring( T ).
  15.  
  16.  
  17.   rev( [], [] ).
  18.   rev( [H|T], L ) :- rev( T,Z), append( Z, [H], L ).
  19.  
  20. /* Recursive member of list definition. 
  21.  
  22. Ask: Member( X, [a,b,c,d,e,f] ) to get successively all
  23. the members of the given list. */
  24.  
  25.  
  26. member( Y, [Y|_] ).
  27.  
  28. member( B, [_|C] ) :-  member( B, C ).
  29.  
  30.  
  31. pp([H|T],I)  :-  !, J is I+3, pp(H,J), ppx(T,J), nl.
  32. pp(X,I)  :- tab(I), print(X), nl.
  33. ppx([],_).
  34. ppx([H|T],I)  :-  pp(H,I),ppx(T,I).
  35.  
  36. /* see page 163 of CM  */
  37.  
  38. findall(X,G,_) :-
  39.       asserta(found(mark)),
  40.       G,
  41.       asserta(found(X)),
  42.       fail.
  43. findall(_,_,L)  :-  collect_found([],M),!, L  =  M.
  44. collect_found(S,L)  :-  getnext(X), !, collect_found([X|S],L).
  45. collect_found(L,L).
  46. getnext(X)  :-  retract(found(X)), !, X \== mark.
  47.  
  48. a(newcastle,carlisle,58).
  49. a(carlisle,penrith,23).
  50. a(darlington,newcastle,40).
  51. a(penrith,darlington,52).
  52. a(workington, carlisle,33).
  53. a(workington, penrith,39).
  54.  
  55. /*  does ; work properly ? */
  56.  
  57. legalnode(X,Trail,Y) :- a(Y,X,_), (not(member(Y,Trail))).
  58. legalnode(X,Trail,Y) :- a(X,Y,_), (not(member(Y,Trail))).
  59.  
  60.  
  61. go(Start,Dest,Route) :-  go1([[Start]],Dest,R), rev(R, Route).
  62. go1([First|Rest],Dest,First) :- First = [Dest|_].
  63. go1([[Last|Trail]|Others],Dest,Route)  :-
  64.       findall([Z,Last|Trail],legalnode(Last,Trail,Z),List),
  65.       append(List,Others,NewRoutes),
  66.       go1(NewRoutes,Dest,Route).
  67.