home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Simtel MSDOS 1992 December
/
simtel1292_SIMTEL_1292_Walnut_Creek.iso
/
msdos
/
prolog
/
prolog19.arc
/
JOURNEY.PRO
< prev
next >
Wrap
Text File
|
1986-05-05
|
2KB
|
67 lines
/*
For a similar program, see Clocksin & Mellish page 165.
Plan a trip from place to place.
An appropriate question would be:
?-go( darlington, workington, X ).
*/
append( [], L, L ).
append( [Z|L1], L2, [Z|L3] ) :- append( L1, L2, L3 ).
printstring( [] ).
printstring( [H|T] ) :- put( H ), printstring( T ).
rev( [], [] ).
rev( [H|T], L ) :- rev( T,Z), append( Z, [H], L ).
/* Recursive member of list definition.
Ask: Member( X, [a,b,c,d,e,f] ) to get successively all
the members of the given list. */
member( Y, [Y|_] ).
member( B, [_|C] ) :- member( 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).
/* see page 163 of CM */
findall(X,G,_) :-
asserta(found(mark)),
G,
asserta(found(X)),
fail.
findall(_,_,L) :- collect_found([],M),!, L = M.
collect_found(S,L) :- getnext(X), !, collect_found([X|S],L).
collect_found(L,L).
getnext(X) :- retract(found(X)), !, X \== mark.
a(newcastle,carlisle,58).
a(carlisle,penrith,23).
a(darlington,newcastle,40).
a(penrith,darlington,52).
a(workington, carlisle,33).
a(workington, penrith,39).
/* does ; work properly ? */
legalnode(X,Trail,Y) :- a(Y,X,_), (not(member(Y,Trail))).
legalnode(X,Trail,Y) :- a(X,Y,_), (not(member(Y,Trail))).
go(Start,Dest,Route) :- go1([[Start]],Dest,R), rev(R, Route).
go1([First|Rest],Dest,First) :- First = [Dest|_].
go1([[Last|Trail]|Others],Dest,Route) :-
findall([Z,Last|Trail],legalnode(Last,Trail,Z),List),
append(List,Others,NewRoutes),
go1(NewRoutes,Dest,Route).