home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Simtel MSDOS 1992 December
/
simtel1292_SIMTEL_1292_Walnut_Creek.iso
/
msdos
/
prolog
/
prolog19.arc
/
OPTJOURN.PRO
< prev
next >
Wrap
Text File
|
1986-05-05
|
2KB
|
86 lines
/* This is a sample network path finding algorithm. To make use of this
see CM (second edition) pages 168-169. You can make use of "look" */
append( [], L, L ).
append( [Z|L1], L2, [Z|L3] ) :- append( L1, L2, L3 ).
printstring( [] ).
printstring( [H|T] ) :- put( H ), printstring( T ).
rev( [], [] ).
rev( [H1|TT], L1 ) :- rev( TT,ZZ), append( ZZ, [H1], L1 ).
/* Recursive member of list definition.
Ask: Member( X, [a,b,c,d,e,f] ) to get successively all
the members of the given list. */
mem( YY, [YY|_] ).
mem( B, [_|C] ) :- mem(B, C ).
pp([H|T],I) :- !, J is I+3, pp(H,J), ppx(T,J), nl.
pp(X,I) :- tab(I), print(X), nl.
ppx([],_).
ppx([H|T],I) :- pp(H,I),ppx(T,I).
a(newcastle,carlisle,58).
a(carlisle,penrith,23).
a(townB,townA,15).
a(penrith,darlington,52).
a(townB,townC,10).
a(workington, carlisle,33).
a(workington,townC,5).
a(workington, penrith,39).
a(darlington,townA,25).
legalnode(X,Trail,Y,Dist,NewDist) :-
(a(X,Y,Z1) ; a(Y,X,Z1)),
not(mem(Y,Trail)),
NewDist is Dist + Z1.
go(Start,End,Travel) :-
go3([r(0,[Start])],End,R55),
rev(R55,Travel).
findall(X5,G,_) :-
asserta(found(mark)),
G,
asserta(found(X5)),
fail.
findall(_,_,L5) :- collect_found([],M5),!, L5 = M5.
collect_found(S,L5) :- getnext(X5), !, collect_found([X5|S],L5).
collect_found(L5,L5).
getnext(X5) :- retract(found(X5)), !, X5 \== mark.
go3(Rts,Dest,Route) :-
shortest(Rts,Shortest,RestRts),
proceed(Shortest,Dest,RestRts,Route).
proceed(r(Dist,Route),Dest,_ ,Route) :- Route = [Dest|_].
proceed(r(Dist,[Last|Trail]),Dest,Rts,Route) :-
findall(r(D1,[Z1,Last|Trail]),
legalnode(Last,Trail,Z1,Dist,D1),List),
append(List,Rts,NewRts),go3(NewRts,Dest,Route).
shortest([Route|Rts],Shortest,[Route|Rest]) :-
shortest(Rts,Shortest,Rest),shorter(Shortest,Route),!.
shortest([Route|Rest],Route,Rest).
shorter(r(M1,_),r(M2,_)) :- M1 < M2.
look :- print('enter the starting location: '),nl,
ratom(Beg),nl,
print('enter the destination: '),
nl,ratom(Dest),
go(Beg,Dest,RRT),
pp( RRT, 1 ).