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

  1.  
  2. /*   This is a sample network path finding algorithm.  To make use of this 
  3. see CM (second edition) pages 168-169.  You can make use of "look" */
  4.  
  5.   append( [], L, L ).
  6.   append( [Z|L1], L2, [Z|L3] ) :- append( L1, L2, L3 ).
  7.   printstring( [] ).
  8.   printstring( [H|T] ) :- put( H ), printstring( T ).
  9.  
  10.  
  11.   rev( [], [] ).
  12.   rev( [H1|TT], L1 ) :- rev( TT,ZZ), append( ZZ, [H1], L1 ).
  13.  
  14. /* Recursive member of list definition. 
  15.  
  16. Ask: Member( X, [a,b,c,d,e,f] ) to get successively all
  17. the members of the given list. */
  18.  
  19.  
  20. mem( YY, [YY|_] ).
  21. mem( B, [_|C] ) :-  mem(B, C ).
  22.  
  23. pp([H|T],I)  :-  !, J is I+3, pp(H,J), ppx(T,J), nl.
  24. pp(X,I)  :- tab(I), print(X), nl.
  25. ppx([],_).
  26. ppx([H|T],I)  :-  pp(H,I),ppx(T,I).
  27.  
  28.  
  29. a(newcastle,carlisle,58).
  30. a(carlisle,penrith,23).
  31. a(townB,townA,15).
  32. a(penrith,darlington,52).
  33. a(townB,townC,10).
  34. a(workington, carlisle,33).
  35. a(workington,townC,5).
  36. a(workington, penrith,39).
  37. a(darlington,townA,25).
  38.  
  39. legalnode(X,Trail,Y,Dist,NewDist) :- 
  40.     (a(X,Y,Z1) ; a(Y,X,Z1)),
  41.     not(mem(Y,Trail)),
  42.     NewDist is Dist + Z1.
  43.  
  44. go(Start,End,Travel) :-
  45.       go3([r(0,[Start])],End,R55),
  46.       rev(R55,Travel).
  47.  
  48. findall(X5,G,_) :-
  49.       asserta(found(mark)),
  50.       G,
  51.       asserta(found(X5)),
  52.       fail.
  53. findall(_,_,L5)  :-  collect_found([],M5),!, L5  =  M5.
  54.  
  55. collect_found(S,L5)  :-  getnext(X5), !, collect_found([X5|S],L5).
  56. collect_found(L5,L5).
  57.  
  58. getnext(X5)  :-  retract(found(X5)), !, X5 \== mark.
  59.  
  60. go3(Rts,Dest,Route) :- 
  61. shortest(Rts,Shortest,RestRts),
  62. proceed(Shortest,Dest,RestRts,Route).
  63.  
  64.  
  65. proceed(r(Dist,Route),Dest,_ ,Route) :- Route = [Dest|_].
  66.  
  67.  
  68. proceed(r(Dist,[Last|Trail]),Dest,Rts,Route)  :- 
  69. findall(r(D1,[Z1,Last|Trail]),
  70. legalnode(Last,Trail,Z1,Dist,D1),List),
  71. append(List,Rts,NewRts),go3(NewRts,Dest,Route).
  72.  
  73.  
  74. shortest([Route|Rts],Shortest,[Route|Rest])  :- 
  75. shortest(Rts,Shortest,Rest),shorter(Shortest,Route),!.
  76. shortest([Route|Rest],Route,Rest).
  77. shorter(r(M1,_),r(M2,_)) :- M1 < M2.
  78.  
  79. look :- print('enter the starting location: '),nl,
  80.          ratom(Beg),nl,
  81.     print('enter the destination: '),
  82.     nl,ratom(Dest),
  83.     go(Beg,Dest,RRT),
  84.     pp( RRT, 1 ).
  85.  
  86.